Enable logging of state changes to stdout

This commit is contained in:
Don Stewart 2007-06-05 08:37:35 +00:00
parent 21e09361a6
commit 7ae7029b50
4 changed files with 13 additions and 4 deletions

View File

@ -99,6 +99,13 @@ defaultLayouts = [ tiled , mirror tiled , full ]
-- Percent of screen to increment by when resizing panes -- Percent of screen to increment by when resizing panes
delta = 3%100 delta = 3%100
--
-- Enable logging of state changes to stdout.
-- The internal state of the window manager is 'shown' in Haskell data format
--
logging :: Bool
logging = False
-- --
-- The key bindings list. -- The key bindings list.
-- --

View File

@ -1,3 +1,4 @@
module Config where module Config where
import Graphics.X11.Xlib.Types (Dimension) import Graphics.X11.Xlib.Types (Dimension)
borderWidth :: Dimension borderWidth :: Dimension
logging :: Bool

View File

@ -45,6 +45,7 @@ main = do
xinesc <- getScreenInfo dpy xinesc <- getScreenInfo dpy
nbc <- initcolor normalBorderColor nbc <- initcolor normalBorderColor
fbc <- initcolor focusedBorderColor fbc <- initcolor focusedBorderColor
hSetBuffering stdout NoBuffering
args <- getArgs args <- getArgs
let winset | ("--resume" : s : _) <- args let winset | ("--resume" : s : _) <- args
@ -89,7 +90,7 @@ main = do
, w <- W.integrate (W.stack wk) ] , w <- W.integrate (W.stack wk) ]
mapM_ manage ws -- find new windows mapM_ manage ws -- find new windows
-- withWindowSet (io . hPrint stderr) -- uncomment for state logging when logging $ withWindowSet (io . hPrint stdout)
-- main loop, for all you HOF/recursion fans out there. -- main loop, for all you HOF/recursion fans out there.
forever $ handle =<< io (nextEvent dpy e >> getEvent e) forever $ handle =<< io (nextEvent dpy e >> getEvent e)

View File

@ -15,7 +15,7 @@ module Operations where
import XMonad import XMonad
import qualified StackSet as W import qualified StackSet as W
import {-# SOURCE #-} Config (borderWidth) import {-# SOURCE #-} Config (borderWidth,logging)
import Data.Maybe import Data.Maybe
import Data.List (genericIndex, intersectBy, partition, delete) import Data.List (genericIndex, intersectBy, partition, delete)
@ -168,8 +168,8 @@ windows f = do
io $ restackWindows d (flt ++ tiled') io $ restackWindows d (flt ++ tiled')
setTopFocus setTopFocus
-- withWindowSet (io . hPrint stderr) -- logging state changes! when logging $ withWindowSet (io . hPrint stdout)
-- io performGC -- really helps -- io performGC -- really helps, but seems to trigger GC bugs?
-- We now go to some effort to compute the minimal set of windows to hide. -- We now go to some effort to compute the minimal set of windows to hide.
-- The minimal set being only those windows which weren't previously hidden, -- The minimal set being only those windows which weren't previously hidden,