mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-02 21:21:52 -07:00
make Layouts able to layout whatever they like.
This commit is contained in:
@@ -84,7 +84,7 @@ borderWidth = 1
|
|||||||
-- |
|
-- |
|
||||||
-- The default set of tiling algorithms
|
-- The default set of tiling algorithms
|
||||||
--
|
--
|
||||||
defaultLayouts :: [Layout]
|
defaultLayouts :: [Layout Window]
|
||||||
defaultLayouts = [ tiled , mirror tiled , full ]
|
defaultLayouts = [ tiled , mirror tiled , full ]
|
||||||
where
|
where
|
||||||
-- default tiling algorithm partitions the screen into two panes
|
-- default tiling algorithm partitions the screen into two panes
|
||||||
|
@@ -368,14 +368,14 @@ instance Message IncMasterN
|
|||||||
|
|
||||||
-- simple fullscreen mode, just render all windows fullscreen.
|
-- simple fullscreen mode, just render all windows fullscreen.
|
||||||
-- a plea for tuple sections: map . (,sc)
|
-- a plea for tuple sections: map . (,sc)
|
||||||
full :: Layout
|
full :: Layout a
|
||||||
full = Layout { doLayout = \sc (W.Stack f _ _) -> return [(f, sc)]
|
full = Layout { doLayout = \sc (W.Stack f _ _) -> return [(f, sc)]
|
||||||
, modifyLayout = const (return 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.
|
||||||
--
|
--
|
||||||
tall :: Int -> Rational -> Rational -> Layout
|
tall :: Int -> Rational -> Rational -> Layout a
|
||||||
tall nmaster delta frac =
|
tall nmaster delta frac =
|
||||||
Layout { doLayout = \r -> return . ap zip (tile frac r nmaster . length) . W.integrate
|
Layout { doLayout = \r -> return . ap zip (tile frac r nmaster . length) . W.integrate
|
||||||
, modifyLayout = \m -> return $ msum [fmap resize (fromMessage m)
|
, modifyLayout = \m -> return $ msum [fmap resize (fromMessage m)
|
||||||
@@ -390,7 +390,7 @@ mirrorRect :: Rectangle -> Rectangle
|
|||||||
mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
mirrorRect (Rectangle rx ry rw rh) = (Rectangle ry rx rh rw)
|
||||||
|
|
||||||
-- | Mirror a layout, compute its 90 degree rotated form.
|
-- | Mirror a layout, compute its 90 degree rotated form.
|
||||||
mirror :: Layout -> Layout
|
mirror :: Layout a -> Layout a
|
||||||
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 (fmap mirror) . ml }
|
, modifyLayout = fmap (fmap mirror) . ml }
|
||||||
|
@@ -43,7 +43,7 @@ data XState = XState
|
|||||||
, statusGaps :: ![(Int,Int,Int,Int)] -- ^ width of status bar on each screen
|
, statusGaps :: ![(Int,Int,Int,Int)] -- ^ width of status bar on each screen
|
||||||
, mapped :: !(S.Set Window) -- ^ the Set of mapped windows
|
, mapped :: !(S.Set Window) -- ^ the Set of mapped windows
|
||||||
, waitingUnmap :: !(M.Map Window Int) -- ^ the number of expected UnmapEvents
|
, waitingUnmap :: !(M.Map Window Int) -- ^ the number of expected UnmapEvents
|
||||||
, layouts :: !(M.Map WorkspaceId (Layout, [Layout])) }
|
, layouts :: !(M.Map WorkspaceId (Layout Window, [Layout Window])) }
|
||||||
-- ^ mapping of workspaces to descriptions of their layouts
|
-- ^ mapping of workspaces to descriptions of their layouts
|
||||||
data XConf = XConf
|
data XConf = XConf
|
||||||
{ display :: Display -- ^ the X11 display
|
{ display :: Display -- ^ the X11 display
|
||||||
@@ -119,10 +119,10 @@ atom_WM_STATE = getAtom "WM_STATE"
|
|||||||
-- 'doLayout', a pure function to layout a Window set 'modifyLayout',
|
-- 'doLayout', a pure function to layout a Window set 'modifyLayout',
|
||||||
-- '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 -> Stack Window -> X [(Window, Rectangle)]
|
data Layout a = Layout { doLayout :: Rectangle -> Stack a -> X [(a, Rectangle)]
|
||||||
, modifyLayout :: SomeMessage -> X (Maybe Layout) }
|
, modifyLayout :: SomeMessage -> X (Maybe (Layout a)) }
|
||||||
|
|
||||||
runLayout :: Layout -> Rectangle -> StackOrNot Window -> X [(Window, Rectangle)]
|
runLayout :: Layout a -> Rectangle -> StackOrNot a -> X [(a, Rectangle)]
|
||||||
runLayout l r = maybe (return []) (doLayout l r)
|
runLayout l r = maybe (return []) (doLayout l r)
|
||||||
|
|
||||||
-- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
|
-- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
|
||||||
|
Reference in New Issue
Block a user