Tomas Janousek 16181ce6e7 Fix MultiToggle crashes with decorated layouts
The problem was that certain layouts keep their "world" state in their value,
which was thrown away and forgotten after ReleaseResources during toggle.

In particular, decorated layouts store some X11 handles in them and
allocate/deallocate it as appropriate. If any modification to their state is
ignored, they may try to deallocate already deallocated memory, which results
in a crash somewhere inside Xlib.

This patch makes Transformers reversible so that nothing is ever ignored. As a
side effect, layout transformers now do receive messages and messages for the
base layout do not need the undo/reapply cycle -- we just pass messages to the
current transformed layout and unapply the transformer when needed.
(This, however, doesn't mean that the base layout is not asked to release
resources on a transformer change -- we still need the transformer to release
its resources and there's no way to do this without asking the base layout as
well.)
2009-12-20 00:47:33 +00:00

112 lines
3.8 KiB
Haskell

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, TypeSynonymInstances #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.Reflect
-- Copyright : (c) Brent Yorgey
-- License : BSD-style (see LICENSE)
--
-- Maintainer : <byorgey@gmail.com>
-- Stability : unstable
-- Portability : unportable
--
-- Reflect a layout horizontally or vertically.
-----------------------------------------------------------------------------
module XMonad.Layout.Reflect (
-- * Usage
-- $usage
reflectHoriz, reflectVert,
REFLECTX(..), REFLECTY(..)
) where
import XMonad.Core
import Graphics.X11 (Rectangle(..), Window)
import Control.Arrow (second)
import XMonad.Layout.LayoutModifier
import XMonad.Layout.MultiToggle
-- $usage
-- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@ file:
--
-- > import XMonad.Layout.Reflect
--
-- and modifying your layoutHook as follows (for example):
--
-- > layoutHook = reflectHoriz $ Tall 1 (3/100) (1/2) -- put master pane on the right
--
-- 'reflectHoriz' and 'reflectVert' can be applied to any sort of
-- layout (including Mirrored layouts) and will simply flip the
-- physical layout of the windows vertically or horizontally.
--
-- "XMonad.Layout.MultiToggle" transformers are also provided for
-- toggling layouts between reflected\/non-reflected with a keybinding.
-- To use this feature, you will also need to import the MultiToggle
-- module:
--
-- > import XMonad.Layout.MultiToggle
--
-- Next, add one or more toggles to your layout. For example, to allow
-- separate toggling of both vertical and horizontal reflection:
--
-- > layoutHook = mkToggle (single REFLECTX) $
-- > mkToggle (single REFLECTY) $
-- > (tiled ||| Mirror tiled ||| ...) -- whatever layouts you use
--
-- Finally, add some keybindings to do the toggling, for example:
--
-- > , ((modm .|. controlMask, xK_x), sendMessage $ Toggle REFLECTX)
-- > , ((modm .|. controlMask, xK_y), sendMessage $ Toggle REFLECTY)
--
-- | Apply a horizontal reflection (left \<--\> right) to a
-- layout.
reflectHoriz :: l a -> ModifiedLayout Reflect l a
reflectHoriz = ModifiedLayout (Reflect Horiz)
-- | Apply a vertical reflection (top \<--\> bottom) to a
-- layout.
reflectVert :: l a -> ModifiedLayout Reflect l a
reflectVert = ModifiedLayout (Reflect Vert)
data ReflectDir = Horiz | Vert
deriving (Read, Show)
-- | Given an axis of reflection and the enclosing rectangle which
-- contains all the laid out windows, transform a rectangle
-- representing a window into its flipped counterpart.
reflectRect :: ReflectDir -> Rectangle -> Rectangle -> Rectangle
reflectRect Horiz (Rectangle sx _ sw _) (Rectangle rx ry rw rh) =
Rectangle (2*sx + fi sw - rx - fi rw) ry rw rh
reflectRect Vert (Rectangle _ sy _ sh) (Rectangle rx ry rw rh) =
Rectangle rx (2*sy + fi sh - ry - fi rh) rw rh
fi :: (Integral a, Num b) => a -> b
fi = fromIntegral
data Reflect a = Reflect ReflectDir deriving (Show, Read)
instance LayoutModifier Reflect a where
-- reflect all the generated Rectangles.
pureModifier (Reflect d) r _ wrs = (map (second $ reflectRect d r) wrs, Just $ Reflect d)
modifierDescription (Reflect d) = "Reflect" ++ xy
where xy = case d of { Horiz -> "X" ; Vert -> "Y" }
-------- instances for MultiToggle ------------------
data REFLECTX = REFLECTX deriving (Read, Show, Eq, Typeable)
data REFLECTY = REFLECTY deriving (Read, Show, Eq, Typeable)
instance Transformer REFLECTX Window where
transform REFLECTX x k = k (reflectHoriz x) (\(ModifiedLayout _ x') -> x')
instance Transformer REFLECTY Window where
transform REFLECTY x k = k (reflectVert x) (\(ModifiedLayout _ x') -> x')