mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
Workspace-specific layouts
This commit is contained in:
parent
bffb0126e0
commit
4fc3448186
21
Config.hs
21
Config.hs
@ -49,10 +49,6 @@ workspaces = 9
|
|||||||
modMask :: KeyMask
|
modMask :: KeyMask
|
||||||
modMask = mod1Mask
|
modMask = mod1Mask
|
||||||
|
|
||||||
-- The default size for the left pane.
|
|
||||||
defaultLeftWidth :: Rational
|
|
||||||
defaultLeftWidth = 1%2
|
|
||||||
|
|
||||||
-- How much to change the size of the windows on the left by default.
|
-- How much to change the size of the windows on the left by default.
|
||||||
defaultDelta :: Rational
|
defaultDelta :: Rational
|
||||||
defaultDelta = 3%100
|
defaultDelta = 3%100
|
||||||
@ -61,16 +57,25 @@ defaultDelta = 3%100
|
|||||||
numlockMask :: KeySym
|
numlockMask :: KeySym
|
||||||
numlockMask = lockMask
|
numlockMask = lockMask
|
||||||
|
|
||||||
-- What layout to start in. See the definition of Layout in XMonad.hs for options.
|
|
||||||
defaultLayout :: Layout
|
|
||||||
defaultLayout = Full
|
-- What layout to start in, and what the default proportion for the
|
||||||
|
-- left pane should be in the tiled layout. See LayoutDesc and
|
||||||
|
-- friends in XMonad.hs for options.
|
||||||
|
startingLayoutDesc :: LayoutDesc
|
||||||
|
startingLayoutDesc = LayoutDesc { layoutType = Full
|
||||||
|
, tileFraction = 1%2
|
||||||
|
}
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
-- The keys list.
|
-- The keys list.
|
||||||
keys :: M.Map (KeyMask, KeySym) (X ())
|
keys :: M.Map (KeyMask, KeySym) (X ())
|
||||||
keys = M.fromList $
|
keys = M.fromList $
|
||||||
[ ((modMask .|. shiftMask, xK_Return), spawn "xterm")
|
[ ((modMask .|. shiftMask, xK_Return), spawn "xterm")
|
||||||
, ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && exec $exe")
|
, ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && exec $exe")
|
||||||
, ((controlMask, xK_space ), spawn "gmrun")
|
-- Stealing Ctrl + Space is evil.
|
||||||
|
-- , ((controlMask, xK_space ), spawn "gmrun")
|
||||||
, ((modMask, xK_Tab ), raise GT)
|
, ((modMask, xK_Tab ), raise GT)
|
||||||
, ((modMask, xK_j ), raise GT)
|
, ((modMask, xK_j ), raise GT)
|
||||||
, ((modMask, xK_k ), raise LT)
|
, ((modMask, xK_k ), raise LT)
|
||||||
|
22
Main.hs
22
Main.hs
@ -41,17 +41,17 @@ main = do
|
|||||||
xinesc <- getScreenInfo dpy
|
xinesc <- getScreenInfo dpy
|
||||||
|
|
||||||
let st = XState
|
let st = XState
|
||||||
{ display = dpy
|
{ display = dpy
|
||||||
, screen = dflt
|
, screen = dflt
|
||||||
, xineScreens = xinesc
|
, xineScreens = xinesc
|
||||||
, wsOnScreen = M.fromList $ map (\n -> (n,n)) [0..((length xinesc)-1)]
|
, wsOnScreen = M.fromList $ map (\n -> (n,n)) [0..((length xinesc)-1)]
|
||||||
, theRoot = rootw
|
, theRoot = rootw
|
||||||
, wmdelete = wmdelt
|
, wmdelete = wmdelt
|
||||||
, wmprotocols = wmprot
|
, wmprotocols = wmprot
|
||||||
, dimensions = (displayWidth dpy dflt, displayHeight dpy dflt)
|
, dimensions = (displayWidth dpy dflt, displayHeight dpy dflt)
|
||||||
, workspace = W.empty workspaces
|
, workspace = W.empty workspaces
|
||||||
, layout = defaultLayout
|
, defaultLayoutDesc = startingLayoutDesc
|
||||||
, leftWidth = defaultLeftWidth
|
, layoutDescs = M.empty
|
||||||
}
|
}
|
||||||
|
|
||||||
xSetErrorHandler -- in C, I'm too lazy to write the binding
|
xSetErrorHandler -- in C, I'm too lazy to write the binding
|
||||||
|
@ -17,6 +17,7 @@ import XMonad
|
|||||||
|
|
||||||
import qualified StackSet as W
|
import qualified StackSet as W
|
||||||
|
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Managing windows
|
-- Managing windows
|
||||||
|
|
||||||
@ -28,8 +29,10 @@ refresh = do
|
|||||||
ws2sc <- gets wsOnScreen
|
ws2sc <- gets wsOnScreen
|
||||||
xinesc <- gets xineScreens
|
xinesc <- gets xineScreens
|
||||||
d <- gets display
|
d <- gets display
|
||||||
l <- gets layout
|
fls <- gets layoutDescs
|
||||||
ratio <- gets leftWidth
|
dfltfl <- gets defaultLayoutDesc
|
||||||
|
-- l <- gets layout
|
||||||
|
-- ratio <- gets leftWidth
|
||||||
let move w a b c e = io $ moveResizeWindow d w a b c e
|
let move w a b c e = io $ moveResizeWindow d w a b c e
|
||||||
flip mapM_ (M.assocs ws2sc) $ \(n, scn) -> do
|
flip mapM_ (M.assocs ws2sc) $ \(n, scn) -> do
|
||||||
let sc = xinesc !! scn
|
let sc = xinesc !! scn
|
||||||
@ -37,6 +40,9 @@ refresh = do
|
|||||||
sy = rect_y sc
|
sy = rect_y sc
|
||||||
sw = rect_width sc
|
sw = rect_width sc
|
||||||
sh = rect_height sc
|
sh = rect_height sc
|
||||||
|
fl = M.findWithDefault dfltfl n fls
|
||||||
|
l = layoutType fl
|
||||||
|
ratio = tileFraction fl
|
||||||
case l of
|
case l of
|
||||||
Full -> whenJust (W.peekStack n ws) $ \w -> do
|
Full -> whenJust (W.peekStack n ws) $ \w -> do
|
||||||
move w sx sy sw sh
|
move w sx sy sw sh
|
||||||
@ -53,20 +59,25 @@ refresh = do
|
|||||||
whenJust (W.peek ws) (io . raiseWindow d) -- this is always Just
|
whenJust (W.peek ws) (io . raiseWindow d) -- this is always Just
|
||||||
whenJust (W.peek ws) setFocus
|
whenJust (W.peek ws) setFocus
|
||||||
|
|
||||||
-- | switchLayout. Switch to another layout scheme.
|
-- | switchLayout. Switch to another layout scheme. Switches the current workspace.
|
||||||
switchLayout :: X ()
|
switchLayout :: X ()
|
||||||
switchLayout = do
|
switchLayout = layout $ \fl -> fl { layoutType = case layoutType fl of
|
||||||
modify (\s -> s {layout = case layout s of
|
Full -> Tile
|
||||||
Full -> Tile
|
Tile -> Full }
|
||||||
Tile -> Full })
|
|
||||||
refresh
|
|
||||||
|
|
||||||
-- | changeWidth. Change the width of the main window in tiling mode.
|
-- | changeWidth. Change the width of the main window in tiling mode.
|
||||||
changeWidth :: Rational -> X ()
|
changeWidth :: Rational -> X ()
|
||||||
changeWidth delta = do
|
changeWidth delta = do
|
||||||
-- the min/max stuff is to make sure that 0 <= leftWidth <= 1
|
layout $ \fl -> fl { tileFraction = min 1 $ max 0 $ tileFraction fl + delta }
|
||||||
modify (\s -> s {leftWidth = min 1 $ max 0 $ leftWidth s + delta})
|
|
||||||
refresh
|
-- | layout. Modify the current workspace's layout with a pure function and refresh.
|
||||||
|
layout :: (LayoutDesc -> LayoutDesc) -> X ()
|
||||||
|
layout f = do modify $ \s -> let fls = layoutDescs s
|
||||||
|
n = W.current . workspace $ s
|
||||||
|
fl = M.findWithDefault (defaultLayoutDesc s) n fls
|
||||||
|
in s { layoutDescs = M.insert n (f fl) fls }
|
||||||
|
refresh
|
||||||
|
|
||||||
|
|
||||||
-- | windows. Modify the current window list with a pure function, and refresh
|
-- | windows. Modify the current window list with a pure function, and refresh
|
||||||
windows :: (WorkSpace -> WorkSpace) -> X ()
|
windows :: (WorkSpace -> WorkSpace) -> X ()
|
||||||
@ -208,3 +219,5 @@ restart :: IO ()
|
|||||||
restart = do prog <- getProgName
|
restart = do prog <- getProgName
|
||||||
args <- getArgs
|
args <- getArgs
|
||||||
executeFile prog True args Nothing
|
executeFile prog True args Nothing
|
||||||
|
|
||||||
|
|
||||||
|
18
XMonad.hs
18
XMonad.hs
@ -15,7 +15,7 @@
|
|||||||
--
|
--
|
||||||
|
|
||||||
module XMonad (
|
module XMonad (
|
||||||
X, WorkSpace, XState(..), Layout(..),
|
X, WorkSpace, XState(..), Layout(..), LayoutDesc(..),
|
||||||
runX, io, withDisplay, isRoot,
|
runX, io, withDisplay, isRoot,
|
||||||
spawn, trace, whenJust
|
spawn, trace, whenJust
|
||||||
) where
|
) where
|
||||||
@ -43,9 +43,13 @@ data XState = XState
|
|||||||
, wmprotocols :: {-# UNPACK #-} !Atom
|
, wmprotocols :: {-# UNPACK #-} !Atom
|
||||||
, dimensions :: {-# UNPACK #-} !(Int,Int)
|
, dimensions :: {-# UNPACK #-} !(Int,Int)
|
||||||
, workspace :: {-# UNPACK #-} !WorkSpace -- ^ workspace list
|
, workspace :: {-# UNPACK #-} !WorkSpace -- ^ workspace list
|
||||||
, layout :: {-# UNPACK #-} !Layout
|
, defaultLayoutDesc :: {-# UNPACK #-} !LayoutDesc
|
||||||
|
, layoutDescs :: {-# UNPACK #-} !(M.Map Int LayoutDesc)
|
||||||
|
-- ^ mapping of workspaces to descriptions of their layouts
|
||||||
|
|
||||||
|
-- , layout :: {-# UNPACK #-} !Layout
|
||||||
-- how much of the screen the main window should take
|
-- how much of the screen the main window should take
|
||||||
, leftWidth :: {-# UNPACK #-} !Rational
|
-- , leftWidth :: {-# UNPACK #-} !Rational
|
||||||
}
|
}
|
||||||
|
|
||||||
type WorkSpace = StackSet Window
|
type WorkSpace = StackSet Window
|
||||||
@ -53,6 +57,14 @@ type WorkSpace = StackSet Window
|
|||||||
-- | The different layout modes
|
-- | The different layout modes
|
||||||
data Layout = Full | Tile
|
data Layout = Full | Tile
|
||||||
|
|
||||||
|
-- | A full description of a particular workspace's layout parameters.
|
||||||
|
data LayoutDesc = LayoutDesc { layoutType :: !Layout
|
||||||
|
, tileFraction :: !Rational
|
||||||
|
}
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
-- | The X monad, a StateT transformer over IO encapuslating the window
|
-- | The X monad, a StateT transformer over IO encapuslating the window
|
||||||
-- manager state
|
-- manager state
|
||||||
newtype X a = X (StateT XState IO a)
|
newtype X a = X (StateT XState IO a)
|
||||||
|
Loading…
x
Reference in New Issue
Block a user