mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-01 12:41:53 -07:00
comments. and stop tracing events to stderr
This commit is contained in:
@@ -42,12 +42,13 @@ import qualified StackSet as W
|
|||||||
refresh :: X ()
|
refresh :: X ()
|
||||||
refresh = do
|
refresh = do
|
||||||
XState { workspace = ws, layoutDescs = fls } <- get
|
XState { workspace = ws, layoutDescs = fls } <- get
|
||||||
XConf { xineScreens = xinesc, display = d } <- ask
|
XConf { xineScreens = xinesc, display = d } <- ask -- neat, eh?
|
||||||
|
|
||||||
flip mapM_ (M.assocs (W.screen2ws ws)) $ \(scn, n) -> do
|
flip mapM_ (M.assocs (W.screen2ws ws)) $ \(scn, n) -> do
|
||||||
let sc = genericIndex xinesc scn -- temporary coercion!
|
let sc = genericIndex xinesc scn -- temporary coercion!
|
||||||
fl = M.findWithDefault defaultLayoutDesc n fls
|
fl = M.findWithDefault defaultLayoutDesc n fls
|
||||||
mapM_ (\(w, rect) -> io $ moveWindowInside d w rect) $
|
mapM_ (\(w, rect) -> io $ moveWindowInside d w rect) $
|
||||||
|
-- likely this should just dispatch on the current layout algo
|
||||||
case layoutType fl of
|
case layoutType fl of
|
||||||
Full -> fmap (flip (,) sc) $ maybeToList $ W.peekStack n ws
|
Full -> fmap (flip (,) sc) $ maybeToList $ W.peekStack n ws
|
||||||
Tall -> tile (tileFraction fl) sc $ W.index n ws
|
Tall -> tile (tileFraction fl) sc $ W.index n ws
|
||||||
@@ -63,11 +64,16 @@ clearEnterEvents = do
|
|||||||
io $ sync d False
|
io $ sync d False
|
||||||
io $ allocaXEvent $ \p -> fix $ \again -> do
|
io $ allocaXEvent $ \p -> fix $ \again -> do
|
||||||
more <- checkMaskEvent d enterWindowMask p
|
more <- checkMaskEvent d enterWindowMask p
|
||||||
when more again
|
when more again -- beautiful
|
||||||
|
|
||||||
-- | tile. Compute the positions for windows in horizontal layout
|
-- | tile. Compute the positions for windows in horizontal layout
|
||||||
-- mode.
|
-- mode.
|
||||||
--
|
--
|
||||||
|
-- Tiling algorithms in the core should satisify the constraint that
|
||||||
|
--
|
||||||
|
-- * no windows overlap
|
||||||
|
-- * no gaps exist between windows.
|
||||||
|
--
|
||||||
tile :: Rational -> Rectangle -> [Window] -> [(Window, Rectangle)]
|
tile :: Rational -> Rectangle -> [Window] -> [(Window, Rectangle)]
|
||||||
tile _ _ [] = []
|
tile _ _ [] = []
|
||||||
tile _ d [w] = [(w, d)]
|
tile _ d [w] = [(w, d)]
|
||||||
@@ -117,8 +123,7 @@ windows :: (WindowSet -> WindowSet) -> X ()
|
|||||||
windows f = do
|
windows f = do
|
||||||
modify $ \s -> s { workspace = f (workspace s) }
|
modify $ \s -> s { workspace = f (workspace s) }
|
||||||
refresh
|
refresh
|
||||||
ws <- gets workspace
|
-- gets workspace >>= trace . show -- log state changes to stderr
|
||||||
trace (show ws) -- log state changes to stderr
|
|
||||||
|
|
||||||
-- | hide. Hide a window by moving it offscreen.
|
-- | hide. Hide a window by moving it offscreen.
|
||||||
hide :: Window -> X ()
|
hide :: Window -> X ()
|
||||||
|
@@ -65,6 +65,11 @@ newtype ScreenId = S Int deriving (Eq,Ord,Show,Enum,Num,Integral,Real)
|
|||||||
|
|
||||||
-- | The X monad, a StateT transformer over IO encapsulating the window
|
-- | The X monad, a StateT transformer over IO encapsulating the window
|
||||||
-- manager state
|
-- manager state
|
||||||
|
--
|
||||||
|
-- Dynamic components may be retrieved with 'get', static components
|
||||||
|
-- with 'ask'. With newtype deriving we get readers and state monads
|
||||||
|
-- instantiated on XConf and XState automatically.
|
||||||
|
--
|
||||||
newtype X a = X (ReaderT XConf (StateT XState IO) a)
|
newtype X a = X (ReaderT XConf (StateT XState IO) a)
|
||||||
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf)
|
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf)
|
||||||
|
|
||||||
@@ -96,8 +101,7 @@ rotateLayout x = if x == maxBound then minBound else succ x
|
|||||||
|
|
||||||
-- | A full description of a particular workspace's layout parameters.
|
-- | A full description of a particular workspace's layout parameters.
|
||||||
data LayoutDesc = LayoutDesc { layoutType :: !Layout
|
data LayoutDesc = LayoutDesc { layoutType :: !Layout
|
||||||
, tileFraction :: !Rational
|
, tileFraction :: !Rational }
|
||||||
}
|
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Utilities
|
-- Utilities
|
||||||
|
Reference in New Issue
Block a user