add new off-center layout combinators.

This commit is contained in:
David Roundy 2007-11-01 21:42:16 +00:00
parent 69999d8018
commit 3e9e9c8b03
2 changed files with 30 additions and 31 deletions

View File

@ -17,7 +17,10 @@
module XMonad.Layout.LayoutCombinators ( module XMonad.Layout.LayoutCombinators (
-- * Usage -- * Usage
-- $usage -- $usage
(<|>), (</>), (<||>), (<//>), (|||), JumpToLayout(JumpToLayout) (<|>), (</>), (<||>), (<//>), (|||), JumpToLayout(JumpToLayout),
(<-/>), (</->), (<-|>), (<|->),
(<-//>), (<//->), (<-||>), (<||->),
) where ) where
import Data.Maybe ( isJust ) import Data.Maybe ( isJust )
@ -30,18 +33,30 @@ import XMonad.Layout.DragPane
-- $usage -- $usage
-- Use LayoutCombinators to easily combine Layouts. -- Use LayoutCombinators to easily combine Layouts.
(<||>), (<//>) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => infixr 6 <||>, <//>, <-||>, <-//>, <||->, <//->, <|>, <-|>, <|->, </>, <-/>, </->
l1 a -> l2 a -> CombineTwo DragPane l1 l2 a
(<|>) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) (<||>), (<//>), (<-||>), (<-//>), (<||->), (<//->)
=> l1 a -> l2 a -> CombineTwo Tall l1 l2 a :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) =>
(</>) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) l1 a -> l2 a -> CombineTwo DragPane l1 l2 a
=> l1 a -> l2 a -> CombineTwo (Mirror Tall) l1 l2 a (<|>), (<-|>), (<|->) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a)
=> l1 a -> l2 a -> CombineTwo Tall l1 l2 a
(</>), (<-/>), (</->) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a)
=> l1 a -> l2 a -> CombineTwo (Mirror Tall) l1 l2 a
(<||>) = combineTwo (dragPane Vertical 0.1 0.5) (<||>) = combineTwo (dragPane Vertical 0.1 0.5)
(<-||>) = combineTwo (dragPane Vertical 0.1 0.2)
(<||->) = combineTwo (dragPane Vertical 0.1 0.8)
(<//>) = combineTwo (dragPane Horizontal 0.1 0.5) (<//>) = combineTwo (dragPane Horizontal 0.1 0.5)
(<-//>) = combineTwo (dragPane Horizontal 0.1 0.2)
(<//->) = combineTwo (dragPane Horizontal 0.1 0.8)
(<|>) = combineTwo (Tall 1 0.1 0.5) (<|>) = combineTwo (Tall 1 0.1 0.5)
(<-|>) = combineTwo (Tall 1 0.1 0.8)
(<|->) = combineTwo (Tall 1 0.1 0.1)
(</>) = combineTwo (Mirror $ Tall 1 0.1 0.5) (</>) = combineTwo (Mirror $ Tall 1 0.1 0.5)
(<-/>) = combineTwo (Mirror $ Tall 1 0.1 0.8)
(</->) = combineTwo (Mirror $ Tall 1 0.1 0.2)
infixr 5 |||
(|||) :: (LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> NewSelect l1 l2 a (|||) :: (LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> NewSelect l1 l2 a
(|||) = NewSelect True (|||) = NewSelect True
@ -88,7 +103,7 @@ instance (LayoutClass l1 a, LayoutClass l2 a) => LayoutClass (NewSelect l1 l2) a
d == description l2 = do ml1' <- handleMessage l1 (SomeMessage Hide) d == description l2 = do ml1' <- handleMessage l1 (SomeMessage Hide)
return $ Just $ NewSelect False (maybe l1 id ml1') l2 return $ Just $ NewSelect False (maybe l1 id ml1') l2
handleMessage (NewSelect True l1 l2) m handleMessage (NewSelect True l1 l2) m
| Just (JumpToLayout d) <- fromMessage m | Just (JumpToLayout _) <- fromMessage m
= do ml1' <- handleMessage l1 m = do ml1' <- handleMessage l1 m
case ml1' of case ml1' of
Just l1' -> return $ Just $ NewSelect True l1' l2 Just l1' -> return $ Just $ NewSelect True l1' l2
@ -103,7 +118,7 @@ instance (LayoutClass l1 a, LayoutClass l2 a) => LayoutClass (NewSelect l1 l2) a
d == description l1 = do ml2' <- handleMessage l2 (SomeMessage Hide) d == description l1 = do ml2' <- handleMessage l2 (SomeMessage Hide)
return $ Just $ NewSelect True l1 (maybe l2 id ml2') return $ Just $ NewSelect True l1 (maybe l2 id ml2')
handleMessage (NewSelect False l1 l2) m handleMessage (NewSelect False l1 l2) m
| Just (JumpToLayout d) <- fromMessage m | Just (JumpToLayout _) <- fromMessage m
= do ml2' <- handleMessage l2 m = do ml2' <- handleMessage l2 m
case ml2' of case ml2' of
Just l2' -> return $ Just $ NewSelect False l1 l2' Just l2' -> return $ Just $ NewSelect False l1 l2'

View File

@ -25,7 +25,6 @@ import qualified XMonad (workspaces, manageHook, numlockMask)
import XMonad.Layouts hiding ( (|||) ) import XMonad.Layouts hiding ( (|||) )
import XMonad.Operations import XMonad.Operations
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import Data.Ratio
import Data.Bits ((.|.)) import Data.Bits ((.|.))
import qualified Data.Map as M import qualified Data.Map as M
import System.Exit import System.Exit
@ -37,7 +36,6 @@ import XMonad.EventLoop
import XMonad.Layout.Tabbed import XMonad.Layout.Tabbed
import XMonad.Layout.Combo import XMonad.Layout.Combo
import XMonad.Layout.LayoutCombinators import XMonad.Layout.LayoutCombinators
import XMonad.Layout.TwoPane
import XMonad.Layout.Square import XMonad.Layout.Square
import XMonad.Layout.LayoutScreens import XMonad.Layout.LayoutScreens
import XMonad.Layout.WindowNavigation import XMonad.Layout.WindowNavigation
@ -158,22 +156,11 @@ layout = -- tiled ||| Mirror tiled ||| Full
-- Add extra layouts you want to use here: -- Add extra layouts you want to use here:
-- % Extension-provided layouts -- % Extension-provided layouts
workspaceDir "~" $ windowNavigation $ toggleLayouts (noBorders Full) $ workspaceDir "~" $ windowNavigation $ toggleLayouts (noBorders Full) $
(noBorders mytab) ||| noBorders mytab |||
(combineTwo (Mirror $ TwoPane 0.03 0.8) mytab (combineTwo Square mytab mytab)) ||| mytab <-/> combineTwo Square mytab mytab |||
(mytab <//> mytab) mytab <//> mytab
where where
mytab = tabbed shrinkText defaultTConf mytab = tabbed shrinkText defaultTConf
-- default tiling algorithm partitions the screen into two panes
tiled = Tall nmaster delta ratio
-- The default number of windows in the master pane
nmaster = 1
-- Default proportion of screen occupied by master pane
ratio = 1%2
-- Percent of screen to increment by when resizing panes
delta = 3%100
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- Key bindings: -- Key bindings:
@ -213,16 +200,12 @@ keys = M.fromList $
-- floating layer support -- floating layer support
, ((modMask, xK_t ), withFocused $ windows . W.sink) -- %! Push window back into tiling , ((modMask, xK_t ), withFocused $ windows . W.sink) -- %! Push window back into tiling
-- increase or decrease number of windows in the master area
, ((modMask , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area
, ((modMask , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area
-- toggle the status bar gap -- toggle the status bar gap
, ((modMask , xK_b ), modifyGap (\i n -> let x = (defaultGaps defaultConfig ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap , ((modMask , xK_b ), modifyGap (\i n -> let x = (defaultGaps defaultConfig ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap
-- quit, or restart -- quit, or restart
, ((modMask .|. shiftMask, xK_Escape), io (exitWith ExitSuccess)) -- %! Quit xmonad , ((modMask .|. shiftMask, xK_Escape), io (exitWith ExitSuccess)) -- %! Quit xmonad
, ((modMask , xK_Escape), broadcastMessage ReleaseResources >> restart Nothing True) -- %! Restart xmonad , ((modMask , xK_Escape), broadcastMessage ReleaseResources >> restart (Just "xmonad-droundy") True) -- %! Restart xmonad
-- % Extension-provided key bindings -- % Extension-provided key bindings
@ -308,7 +291,7 @@ defaultConfig = XConfig { borderWidth = 1 -- Width of the window border in pixel
, layoutHook = Layout layout , layoutHook = Layout layout
, terminal = "xterm" -- The preferred terminal program. , terminal = "xterm" -- The preferred terminal program.
, normalBorderColor = "#dddddd" -- Border color for unfocused windows. , normalBorderColor = "#dddddd" -- Border color for unfocused windows.
, focusedBorderColor = "#ff0000" -- Border color for focused windows. , focusedBorderColor = "#00ff00" -- Border color for focused windows.
, XMonad.numlockMask = numlockMask , XMonad.numlockMask = numlockMask
, XMonad.keys = Main.keys , XMonad.keys = Main.keys
, XMonad.mouseBindings = Main.mouseBindings , XMonad.mouseBindings = Main.mouseBindings
@ -322,4 +305,5 @@ defaultConfig = XConfig { borderWidth = 1 -- Width of the window border in pixel
, XMonad.manageHook = manageHook , XMonad.manageHook = manageHook
} }
main :: IO ()
main = makeMain defaultConfig main = makeMain defaultConfig