mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
implement Spencer's decoration suggestion.
This commit is contained in:
parent
e1885f27e1
commit
ab6f210300
4
Main.hs
4
Main.hs
@ -224,4 +224,6 @@ handle e@(ConfigureRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
|
|||||||
-- the root may have configured
|
-- the root may have configured
|
||||||
handle (ConfigureEvent {ev_window = w}) = whenX (isRoot w) rescreen
|
handle (ConfigureEvent {ev_window = w}) = whenX (isRoot w) rescreen
|
||||||
|
|
||||||
handle _ = return () -- trace (eventName e) -- ignoring
|
handle e = sendMessage e -- trace (eventName e) -- ignoring
|
||||||
|
|
||||||
|
instance Message Event
|
||||||
|
@ -335,7 +335,11 @@ switchLayout = layout (\(x, xs) -> let xs' = xs ++ [x] in (head xs', tail xs'))
|
|||||||
-- TODO, this will refresh on Nothing.
|
-- TODO, this will refresh on Nothing.
|
||||||
--
|
--
|
||||||
sendMessage :: Message a => a -> X ()
|
sendMessage :: Message a => a -> X ()
|
||||||
sendMessage a = layout $ \x@(l, ls) -> maybe x (flip (,) ls) (modifyLayout l (SomeMessage a))
|
sendMessage a = do n <- (W.tag . W.workspace . W.current) `fmap` gets windowset
|
||||||
|
Just (l,ls) <- M.lookup n `fmap` gets layouts
|
||||||
|
ml' <- modifyLayout l (SomeMessage a)
|
||||||
|
whenJust ml' $ \l' -> do modify $ \s -> s { layouts = M.insert n (l',ls) (layouts s) }
|
||||||
|
refresh
|
||||||
|
|
||||||
--
|
--
|
||||||
-- Builtin layout algorithms:
|
-- Builtin layout algorithms:
|
||||||
@ -358,7 +362,7 @@ instance Message IncMasterN
|
|||||||
-- a plea for tuple sections: map . (,sc)
|
-- a plea for tuple sections: map . (,sc)
|
||||||
full :: Layout
|
full :: Layout
|
||||||
full = Layout { doLayout = \sc ws -> return [ (w,sc) | w <- ws ]
|
full = Layout { doLayout = \sc ws -> return [ (w,sc) | w <- ws ]
|
||||||
, modifyLayout = const Nothing } -- no changes
|
, modifyLayout = const (return Nothing) } -- no changes
|
||||||
|
|
||||||
--
|
--
|
||||||
-- The tiling mode of xmonad, and its operations.
|
-- The tiling mode of xmonad, and its operations.
|
||||||
@ -366,8 +370,8 @@ full = Layout { doLayout = \sc ws -> return [ (w,sc) | w <- ws ]
|
|||||||
tall :: Int -> Rational -> Rational -> Layout
|
tall :: Int -> Rational -> Rational -> Layout
|
||||||
tall nmaster delta frac =
|
tall nmaster delta frac =
|
||||||
Layout { doLayout = \r -> return . ap zip (tile frac r nmaster . length)
|
Layout { doLayout = \r -> return . ap zip (tile frac r nmaster . length)
|
||||||
, modifyLayout = \m -> fmap resize (fromMessage m) `mplus`
|
, modifyLayout = \m -> return $ msum [fmap resize (fromMessage m)
|
||||||
fmap incmastern (fromMessage m) }
|
,fmap incmastern (fromMessage m)] }
|
||||||
|
|
||||||
where resize Shrink = tall nmaster delta (frac-delta)
|
where resize Shrink = tall nmaster delta (frac-delta)
|
||||||
resize Expand = tall nmaster delta (frac+delta)
|
resize Expand = tall nmaster delta (frac+delta)
|
||||||
@ -381,7 +385,7 @@ mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
|||||||
mirror :: Layout -> Layout
|
mirror :: Layout -> Layout
|
||||||
mirror (Layout { doLayout = dl, modifyLayout = ml }) =
|
mirror (Layout { doLayout = dl, modifyLayout = ml }) =
|
||||||
Layout { doLayout = \sc w -> map (second mirrorRect) `fmap` dl (mirrorRect sc) w
|
Layout { doLayout = \sc w -> map (second mirrorRect) `fmap` dl (mirrorRect sc) w
|
||||||
, modifyLayout = fmap mirror . ml }
|
, modifyLayout = fmap (fmap mirror) . ml }
|
||||||
|
|
||||||
-- | tile. Compute the positions for windows using the default 2 pane tiling algorithm.
|
-- | tile. Compute the positions for windows using the default 2 pane tiling algorithm.
|
||||||
--
|
--
|
||||||
|
@ -109,7 +109,7 @@ atom_WM_STATE = getAtom "WM_STATE"
|
|||||||
-- 'modifyLayout' can be considered a branch of an exception handler.
|
-- 'modifyLayout' can be considered a branch of an exception handler.
|
||||||
--
|
--
|
||||||
data Layout = Layout { doLayout :: Rectangle -> [Window] -> X [(Window, Rectangle)]
|
data Layout = Layout { doLayout :: Rectangle -> [Window] -> X [(Window, Rectangle)]
|
||||||
, modifyLayout :: SomeMessage -> Maybe Layout }
|
, modifyLayout :: SomeMessage -> X (Maybe Layout) }
|
||||||
|
|
||||||
-- Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
|
-- Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
|
||||||
-- Simon Marlow, 2006. Use extensible messages to the modifyLayout handler.
|
-- Simon Marlow, 2006. Use extensible messages to the modifyLayout handler.
|
||||||
|
Loading…
x
Reference in New Issue
Block a user