| Copyright | (c) 2007 Andrea Rossato 2009 Jan Vornberger | 
|---|---|
| License | BSD-style (see xmonad/LICENSE) | 
| Maintainer | andrea.rossato@unibz.it | 
| Stability | unstable | 
| Portability | unportable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
XMonad.Layout.Decoration
Contents
Description
A layout modifier and a class for easily creating decorated layouts.
Synopsis
- decoration :: (DecorationStyle ds a, Shrinker s) => s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
 - data Theme = Theme {
- activeColor :: String
 - inactiveColor :: String
 - urgentColor :: String
 - activeBorderColor :: String
 - inactiveBorderColor :: String
 - urgentBorderColor :: String
 - activeBorderWidth :: Dimension
 - inactiveBorderWidth :: Dimension
 - urgentBorderWidth :: Dimension
 - activeTextColor :: String
 - inactiveTextColor :: String
 - urgentTextColor :: String
 - fontName :: String
 - decoWidth :: Dimension
 - decoHeight :: Dimension
 - windowTitleAddons :: [(String, Align)]
 - windowTitleIcons :: [([[Bool]], Placement)]
 
 - def :: Default a => a
 - data Decoration (ds :: Type -> Type) s a
 - newtype DecorationMsg = SetTheme Theme
 - class (Read (ds a), Show (ds a), Eq a) => DecorationStyle (ds :: Type -> Type) a where
- describeDeco :: ds a -> String
 - shrink :: ds a -> Rectangle -> Rectangle -> Rectangle
 - decorationEventHook :: ds a -> DecorationState -> Event -> X ()
 - decorationCatchClicksHook :: ds a -> Window -> Int -> Int -> X Bool
 - decorationWhileDraggingHook :: ds a -> CInt -> CInt -> (Window, Rectangle) -> Position -> Position -> X ()
 - decorationAfterDraggingHook :: ds a -> (Window, Rectangle) -> Window -> X ()
 - pureDecoration :: ds a -> Dimension -> Dimension -> Rectangle -> Stack a -> [(a, Rectangle)] -> (a, Rectangle) -> Maybe Rectangle
 - decorate :: ds a -> Dimension -> Dimension -> Rectangle -> Stack a -> [(a, Rectangle)] -> (a, Rectangle) -> X (Maybe Rectangle)
 
 - data DefaultDecoration a = DefaultDecoration
 - class (Read s, Show s) => Shrinker s where
 - data DefaultShrinker
 - shrinkText :: DefaultShrinker
 - data CustomShrink = CustomShrink
 - shrinkWhile :: (String -> [String]) -> (String -> X Bool) -> String -> X String
 - isInStack :: Eq a => Stack a -> a -> Bool
 - isVisible :: Rectangle -> [Rectangle] -> Bool
 - isInvisible :: Rectangle -> [Rectangle] -> Bool
 - isWithin :: Rectangle -> Rectangle -> Bool
 - fi :: (Integral a, Num b) => a -> b
 - findWindowByDecoration :: Window -> DecorationState -> Maybe (OrigWin, (Window, Maybe Rectangle))
 - module XMonad.Layout.LayoutModifier
 - data DecorationState
 - type OrigWin = (Window, Rectangle)
 
Usage:
This module is intended for layout developers, who want to decorate their layouts. End users will not find here very much for them.
For examples of DecorationStyle instances you can have a look at
 XMonad.Layout.SimpleDecoration, XMonad.Layout.Tabbed,
 XMonad.Layout.DwmStyle, or XMonad.Layout.TabBarDecoration.
decoration :: (DecorationStyle ds a, Shrinker s) => s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a Source #
A layout modifier that, with a Shrinker, a Theme, a
 DecorationStyle, and a layout, will decorate this layout
 according to the decoration style provided.
For some usage examples see XMonad.Layout.DecorationMadness.
A Theme is a record of colors, font etc., to customize a
 DecorationStyle.
For a collection of Themes see XMonad.Util.Themes
Constructors
| Theme | |
Fields 
  | |
data Decoration (ds :: Type -> Type) s a Source #
The Decoration 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
 DecorationStyle.
Instances
| (DecorationStyle ds Window, Shrinker s) => LayoutModifier (Decoration ds s) Window Source # | The long  In  The state is  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   | 
Defined in XMonad.Layout.Decoration Methods modifyLayout :: LayoutClass l Window => Decoration ds s Window -> Workspace WorkspaceId (l Window) Window -> Rectangle -> X ([(Window, Rectangle)], Maybe (l Window)) Source # modifyLayoutWithUpdate :: LayoutClass l Window => Decoration ds s Window -> Workspace WorkspaceId (l Window) Window -> Rectangle -> X (([(Window, Rectangle)], Maybe (l Window)), Maybe (Decoration ds s Window)) Source # handleMess :: Decoration ds s Window -> SomeMessage -> X (Maybe (Decoration ds s Window)) Source # handleMessOrMaybeModifyIt :: Decoration ds s Window -> SomeMessage -> X (Maybe (Either (Decoration ds s Window) SomeMessage)) Source # pureMess :: Decoration ds s Window -> SomeMessage -> Maybe (Decoration ds s Window) Source # redoLayout :: Decoration ds s Window -> Rectangle -> Maybe (Stack Window) -> [(Window, Rectangle)] -> X ([(Window, Rectangle)], Maybe (Decoration ds s Window)) Source # pureModifier :: Decoration ds s Window -> Rectangle -> Maybe (Stack Window) -> [(Window, Rectangle)] -> ([(Window, Rectangle)], Maybe (Decoration ds s Window)) Source # hook :: Decoration ds s Window -> X () Source # unhook :: Decoration ds s Window -> X () Source # modifierDescription :: Decoration ds s Window -> String Source # modifyDescription :: LayoutClass l Window => Decoration ds s Window -> l Window -> String Source #  | |
| (Read s, Read (ds a)) => Read (Decoration ds s a) Source # | |
Defined in XMonad.Layout.Decoration Methods readsPrec :: Int -> ReadS (Decoration ds s a) # readList :: ReadS [Decoration ds s a] # readPrec :: ReadPrec (Decoration ds s a) # readListPrec :: ReadPrec [Decoration ds s a] #  | |
| (Show s, Show (ds a)) => Show (Decoration ds s a) Source # | |
Defined in XMonad.Layout.Decoration Methods showsPrec :: Int -> Decoration ds s a -> ShowS # show :: Decoration ds s a -> String # showList :: [Decoration ds s a] -> ShowS #  | |
newtype DecorationMsg Source #
A Decoration layout modifier will handle SetTheme, a message
 to dynamically change the decoration Theme.
Instances
| Message DecorationMsg Source # | |
Defined in XMonad.Layout.Decoration  | |
class (Read (ds a), Show (ds a), Eq a) => DecorationStyle (ds :: Type -> Type) a where Source #
The DecorationStyle class, defines methods used in the
 implementation of the Decoration LayoutModifier instance. A
 type instance of this class is passed to the Decoration type in
 order to decorate a layout, by using these methods.
Minimal complete definition
Nothing
Methods
describeDeco :: ds a -> String Source #
The description that the Decoration modifier will display.
shrink :: ds a -> Rectangle -> Rectangle -> Rectangle Source #
Shrink the window's rectangle when applying a decoration.
decorationEventHook :: ds a -> DecorationState -> Event -> X () Source #
The decoration event hook
decorationCatchClicksHook Source #
Arguments
| :: ds a | |
| -> Window | |
| -> Int | distance from the left where the click happened on the decoration  | 
| -> Int | distance from the right where the click happened on the decoration  | 
| -> X Bool | 
A hook that can be used to catch the cases when the user clicks on the decoration. If you return True here, the click event will be considered as dealt with and no further processing will take place.
decorationWhileDraggingHook :: ds a -> CInt -> CInt -> (Window, Rectangle) -> Position -> Position -> X () Source #
This hook is called while a window is dragged using the decoration. The hook can be overwritten if a different way of handling the dragging is required.
decorationAfterDraggingHook :: ds a -> (Window, Rectangle) -> Window -> X () Source #
This hoook is called after a window has been dragged using the decoration.
pureDecoration :: ds a -> Dimension -> Dimension -> Rectangle -> Stack a -> [(a, Rectangle)] -> (a, Rectangle) -> Maybe Rectangle Source #
The pure version of the main method, decorate.
decorate :: ds a -> Dimension -> Dimension -> Rectangle -> Stack a -> [(a, Rectangle)] -> (a, Rectangle) -> X (Maybe Rectangle) Source #
Instances
data DefaultDecoration a Source #
The default DecorationStyle, with just the default methods'
 implementations.
Constructors
| DefaultDecoration | 
Instances
class (Read s, Show s) => Shrinker s where Source #
Instances
| Shrinker CustomShrink Source # | |
Defined in XMonad.Config.Droundy  | |
| Shrinker DefaultShrinker Source # | |
Defined in XMonad.Layout.Decoration  | |
data DefaultShrinker Source #
Instances
| Read DefaultShrinker Source # | |
Defined in XMonad.Layout.Decoration Methods readsPrec :: Int -> ReadS DefaultShrinker # readList :: ReadS [DefaultShrinker] #  | |
| Show DefaultShrinker Source # | |
Defined in XMonad.Layout.Decoration Methods showsPrec :: Int -> DefaultShrinker -> ShowS # show :: DefaultShrinker -> String # showList :: [DefaultShrinker] -> ShowS #  | |
| Shrinker DefaultShrinker Source # | |
Defined in XMonad.Layout.Decoration  | |
data CustomShrink Source #
Constructors
| CustomShrink | 
Instances
| Read CustomShrink Source # | |
Defined in XMonad.Layout.Decoration Methods readsPrec :: Int -> ReadS CustomShrink # readList :: ReadS [CustomShrink] #  | |
| Show CustomShrink Source # | |
Defined in XMonad.Layout.Decoration Methods showsPrec :: Int -> CustomShrink -> ShowS # show :: CustomShrink -> String # showList :: [CustomShrink] -> ShowS #  | |
| Shrinker CustomShrink Source # | |
Defined in XMonad.Config.Droundy  | |
findWindowByDecoration :: Window -> DecorationState -> Maybe (OrigWin, (Window, Maybe Rectangle)) Source #
module XMonad.Layout.LayoutModifier
data DecorationState Source #
The Decoration state component, where the list of decorated
 window's is zipped with a list of decoration. A list of decoration
 is a list of tuples, a Maybe Window and a 'Maybe Rectangle'.
 The Window will be displayed only if the rectangle is of type
 Just.