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

40 lines
1.5 KiB
Haskell

{-# LANGUAGE TypeSynonymInstances, DeriveDataTypeable, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.MultiToggle.Instances
-- Copyright : (c) 2008 Brent Yorgey
-- License : BSD-style (see LICENSE)
--
-- Maintainer : <byorgey@gmail.com>
-- Stability : unstable
-- Portability : unportable
--
-- Some convenient common instances of the
-- 'XMonad.Layout.MultiToggle.Transformer' class, for use with
-- "XMonad.Layout.MultiToggle".
module XMonad.Layout.MultiToggle.Instances (
StdTransformers(..)
) where
import XMonad.Layout.MultiToggle
import XMonad
import XMonad.Layout.NoBorders
import XMonad.Layout.LayoutModifier
data StdTransformers = FULL -- ^ switch to Full layout
| NBFULL -- ^ switch to Full with no borders
| MIRROR -- ^ Mirror the current layout.
| NOBORDERS -- ^ Remove borders.
| SMARTBORDERS -- ^ Apply smart borders.
deriving (Read, Show, Eq, Typeable)
instance Transformer StdTransformers Window where
transform FULL x k = k Full (const x)
transform NBFULL x k = k (noBorders Full) (const x)
transform MIRROR x k = k (Mirror x) (\(Mirror x') -> x')
transform NOBORDERS x k = k (noBorders x) (\(ModifiedLayout _ x') -> x')
transform SMARTBORDERS x k = k (smartBorders x) (\(ModifiedLayout _ x') -> x')