From b7aaefbace2867206bd77f19660f7ae6c628fdb5 Mon Sep 17 00:00:00 2001 From: David Roundy Date: Fri, 21 Sep 2007 22:43:16 +0200 Subject: make layouts preserved over restart darcs-hash:20070921204316-72aca-6f8cabc516cc87345bfa73be0e060b206aa2a207.gz --- Operations.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) (limited to 'Operations.hs') diff --git a/Operations.hs b/Operations.hs index 8b470e7..dc7a16b 100644 --- a/Operations.hs +++ b/Operations.hs @@ -18,7 +18,7 @@ module Operations where import XMonad import qualified StackSet as W -import {-# SOURCE #-} Config (borderWidth,logHook,numlockMask) +import {-# SOURCE #-} Config (borderWidth,logHook,numlockMask,defaultLayouts) import Data.Maybe import Data.List (nub, (\\), find) @@ -105,6 +105,12 @@ kill = withDisplay $ \d -> withFocused $ \w -> do data UnDoLayout = UnDoLayout deriving ( Typeable, Eq ) instance Message UnDoLayout +instance Read (SomeLayout Window) where + readsPrec _ = readLayout defaultLayouts +instance Layout SomeLayout Window where + doLayout (SomeLayout l) r s = fmap (fmap $ fmap SomeLayout) $ doLayout l r s + modifyLayout (SomeLayout l) = fmap (fmap SomeLayout) . modifyLayout l + -- | windows. Modify the current window list with a pure function, and refresh windows :: (WindowSet -> WindowSet) -> X () windows f = do -- cgit v1.2.3