xmonad-contrib-0.18.0.9: Community-maintained extensions for xmonad
Copyright(c) 2008 Quentin Moser
LicenseBSD3
Maintainerorphaned
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Layout.MessageControl

Contents

Description

Provides message "escaping" and filtering facilities which help control complex nested layouts.

Synopsis

Usage

You can use this module by importing it into your xmonad.hs file:

import XMonad.Layout.MessageEscape

Then, if you use a modified layout where the modifier would intercept a message, but you'd want to be able to send it to the inner layout only, add the unEscape modifier to the inner layout like so:

import XMonad.Layout.Master (mastered)
import XMonad.Layout.Tabbed (simpleTabbed)

myLayout = Tall ||| unEscape (mastered 0.01 0.5 $ Full ||| simpleTabbed)

you can now send a message to the inner layout with sendMessage $ escape message, e.g.

-- Change the inner layout
((modm .|. controlMask, xK_space), sendMessage $ escape NextLayout)

If you want unescaped messages to be handled only by the enclosing layout, use the ignore modifier:

myLayout = Tall ||| (ignore NextLayout $ ignore (JumpToLayout "") $
                      unEscape $ mastered 0.01 0.5
                        $ Full ||| simpleTabbed)

data Ignore m l w Source #

the Ignore layout modifier. Prevents its inner layout from receiving messages of a certain type.

Instances

Instances details
(Message m, LayoutClass l w) => LayoutClass (Ignore m l) w Source # 
Instance details

Defined in XMonad.Layout.MessageControl

Methods

runLayout :: Workspace WorkspaceId (Ignore m l w) w -> Rectangle -> X ([(w, Rectangle)], Maybe (Ignore m l w)) #

doLayout :: Ignore m l w -> Rectangle -> Stack w -> X ([(w, Rectangle)], Maybe (Ignore m l w)) #

pureLayout :: Ignore m l w -> Rectangle -> Stack w -> [(w, Rectangle)] #

emptyLayout :: Ignore m l w -> Rectangle -> X ([(w, Rectangle)], Maybe (Ignore m l w)) #

handleMessage :: Ignore m l w -> SomeMessage -> X (Maybe (Ignore m l w)) #

pureMessage :: Ignore m l w -> SomeMessage -> Maybe (Ignore m l w) #

description :: Ignore m l w -> String #

Read (l w) => Read (Ignore m l w) Source # 
Instance details

Defined in XMonad.Layout.MessageControl

Methods

readsPrec :: Int -> ReadS (Ignore m l w) #

readList :: ReadS [Ignore m l w] #

readPrec :: ReadPrec (Ignore m l w) #

readListPrec :: ReadPrec [Ignore m l w] #

Show (l w) => Show (Ignore m l w) Source # 
Instance details

Defined in XMonad.Layout.MessageControl

Methods

showsPrec :: Int -> Ignore m l w -> ShowS #

show :: Ignore m l w -> String #

showList :: [Ignore m l w] -> ShowS #

ignore :: (Message m, LayoutClass l w) => m -> l w -> Ignore m l w Source #

Applies the Ignore layout modifier to a layout, blocking all messages of the same type as the one passed as its first argument.

data UnEscape w Source #

the UnEscape layout modifier. Listens to EscapedMessages and sends their nested message to the inner layout.

Instances

Instances details
LayoutModifier UnEscape a Source # 
Instance details

Defined in XMonad.Layout.MessageControl

Read (UnEscape w) Source # 
Instance details

Defined in XMonad.Layout.MessageControl

Show (UnEscape w) Source # 
Instance details

Defined in XMonad.Layout.MessageControl

Methods

showsPrec :: Int -> UnEscape w -> ShowS #

show :: UnEscape w -> String #

showList :: [UnEscape w] -> ShowS #

unEscape :: LayoutClass l w => l w -> ModifiedLayout UnEscape l w Source #

Applies the UnEscape layout modifier to a layout.

newtype EscapedMessage Source #

Data type for an escaped message. Send with escape.

Constructors

Escape SomeMessage 

Instances

Instances details
Message EscapedMessage Source # 
Instance details

Defined in XMonad.Layout.MessageControl