clean up names of layout code

This commit is contained in:
Don Stewart
2007-10-13 20:43:00 +00:00
parent f5bec53b83
commit 775172983b
4 changed files with 60 additions and 53 deletions

View File

@@ -115,22 +115,13 @@ focusedBorderColor = "#ff0000"
borderWidth :: Dimension borderWidth :: Dimension
borderWidth = 1 borderWidth = 1
-- | -- | The list of possible layouts. Add your custom layouts to this list.
-- The default Layout, a selector between the layouts listed below in layouts :: [Layout Window]
-- defaultLayouts. layouts = [ Layout tiled
-- , Layout $ Mirror tiled
defaultLayout :: Layout Window , Layout Full
defaultLayout = Layout $ LayoutSelection defaultLayouts -- Add extra layouts you want to use here:
]
-- |
-- The list of selectable layouts
defaultLayouts :: [Layout Window]
defaultLayouts = [ Layout tiled
, Layout $ Mirror tiled
, Layout Full
-- Extension-provided layouts
]
where where
-- default tiling algorithm partitions the screen into two panes -- default tiling algorithm partitions the screen into two panes
tiled = Tall nmaster delta ratio tiled = Tall nmaster delta ratio
@@ -145,11 +136,24 @@ defaultLayouts = [ Layout tiled
delta = 3%100 delta = 3%100
-- | -- |
-- A list of layouts which xmonad can deserialize. -- The top level layout switcher. By default, we simply switch between
possibleLayouts :: [Layout Window] -- the layouts listed in `layouts', but you may program your own selection
possibleLayouts = [defaultLayout -- behaviour here. Layout transformers would be hooked in here.
-- Extension-provided layouts --
] ++ defaultLayouts layoutHook :: Layout Window
layoutHook = Layout $ Select layouts
-- |
-- The default Layout, a selector between the layouts listed below in
-- defaultLayouts.
--
-- defaultLayout :: Layout Window
-- defaultLayout = Layout $ LayoutSelection defaultLayouts
-- | Register with xmonad a list of layouts whose state we can preserve over restarts.
-- There is typically no need to modify this list, the defaults are fine.
serialisedLayouts :: [Layout Window]
serialisedLayouts = layoutHook : layouts
-- | -- |
-- Perform an arbitrary action on each state change. -- Perform an arbitrary action on each state change.
@@ -175,7 +179,7 @@ keys = M.fromList $
, ((modMask .|. shiftMask, xK_c ), kill) -- %! Close the focused window , ((modMask .|. shiftMask, xK_c ), kill) -- %! Close the focused window
, ((modMask, xK_space ), sendMessage NextLayout) -- %! Rotate through the available layout algorithms , ((modMask, xK_space ), sendMessage NextLayout) -- %! Rotate through the available layout algorithms
, ((modMask .|. shiftMask, xK_space ), setLayout defaultLayout) -- %! Reset the layouts on the current workspace to default , ((modMask .|. shiftMask, xK_space ), setLayout layoutHook) -- %! Reset the layouts on the current workspace to default
, ((modMask, xK_n ), refresh) -- %! Resize viewed windows to the correct size , ((modMask, xK_n ), refresh) -- %! Resize viewed windows to the correct size

View File

@@ -3,8 +3,8 @@ import Graphics.X11.Xlib.Types (Dimension)
import Graphics.X11.Xlib (KeyMask,Window) import Graphics.X11.Xlib (KeyMask,Window)
import XMonad import XMonad
borderWidth :: Dimension borderWidth :: Dimension
logHook :: X ()
numlockMask :: KeyMask numlockMask :: KeyMask
workspaces :: [WorkspaceId] workspaces :: [WorkspaceId]
possibleLayouts :: [Layout Window] logHook :: X ()
manageHook :: Window -> String -> String -> String -> X (WindowSet -> WindowSet) manageHook :: Window -> String -> String -> String -> X (WindowSet -> WindowSet)
serialisedLayouts :: [Layout Window]

View File

@@ -50,7 +50,7 @@ main = do
hSetBuffering stdout NoBuffering hSetBuffering stdout NoBuffering
args <- getArgs args <- getArgs
let initialWinset = new defaultLayout workspaces $ zipWith SD xinesc gaps let initialWinset = new layoutHook workspaces $ zipWith SD xinesc gaps
maybeRead s = case reads s of maybeRead s = case reads s of
[(x, "")] -> Just x [(x, "")] -> Just x
@@ -59,8 +59,8 @@ main = do
winset = fromMaybe initialWinset $ do winset = fromMaybe initialWinset $ do
("--resume" : s : _) <- return args ("--resume" : s : _) <- return args
ws <- maybeRead s ws <- maybeRead s
return . W.ensureTags defaultLayout workspaces return . W.ensureTags layoutHook workspaces
$ W.mapLayout (fromMaybe defaultLayout . maybeRead) ws $ W.mapLayout (fromMaybe layoutHook . maybeRead) ws
gaps = take (length xinesc) $ defaultGaps ++ repeat (0,0,0,0) gaps = take (length xinesc) $ defaultGaps ++ repeat (0,0,0,0)

View File

@@ -20,7 +20,7 @@ module Operations where
import XMonad import XMonad
import qualified StackSet as W import qualified StackSet as W
import {-# SOURCE #-} Config (borderWidth,logHook,manageHook,numlockMask,possibleLayouts) import {-# SOURCE #-} Config (borderWidth,logHook,manageHook,numlockMask,serialisedLayouts)
import Data.Maybe import Data.Maybe
import Data.List (nub, (\\), find, partition) import Data.List (nub, (\\), find, partition)
@@ -360,46 +360,49 @@ data ChangeLayout = NextLayout | PrevLayout | JumpToLayout String
instance Message ChangeLayout instance Message ChangeLayout
instance ReadableLayout Window where instance ReadableLayout Window where
defaults = Layout (LayoutSelection []) : defaults = Layout (Select []) :
Layout Full : Layout (Tall 1 0.1 0.5) : Layout Full : Layout (Tall 1 0.1 0.5) :
Layout (Mirror $ Tall 1 0.1 0.5) : Layout (Mirror $ Tall 1 0.1 0.5) :
possibleLayouts serialisedLayouts
data LayoutSelection a = LayoutSelection [Layout a] data Select a = Select [Layout a] deriving (Show, Read)
deriving ( Show, Read )
instance ReadableLayout a => LayoutClass Select a where
doLayout (Select (l:ls)) r s = do
(x,ml') <- doLayout l r s
return (x, (\l' -> Select (l':ls)) `fmap` ml')
doLayout (Select []) r s = do
(x,_) <- doLayout Full r s
return (x,Nothing)
instance ReadableLayout a => LayoutClass LayoutSelection a where
doLayout (LayoutSelection (l:ls)) r s =
do (x,ml') <- doLayout l r s
return (x, (\l' -> LayoutSelection (l':ls)) `fmap` ml')
doLayout (LayoutSelection []) r s = do (x,_) <- doLayout Full r s
return (x,Nothing)
-- respond to messages only when there's an actual choice: -- respond to messages only when there's an actual choice:
handleMessage (LayoutSelection (l:ls@(_:_))) m handleMessage (Select (l:ls@(_:_))) m
| Just NextLayout <- fromMessage m = switchl rls | Just NextLayout <- fromMessage m = switchl rls
| Just PrevLayout <- fromMessage m = switchl rls' | Just PrevLayout <- fromMessage m = switchl rls'
| Just (JumpToLayout x) <- fromMessage m = switchl (j x) | Just (JumpToLayout x) <- fromMessage m = switchl (j x)
| Just ReleaseResources <- fromMessage m = | Just ReleaseResources <- fromMessage m =
do mlls' <- mapM (\ll -> handleMessage ll m) (l:ls) do mlls' <- mapM (\ll -> handleMessage ll m) (l:ls)
let lls' = zipWith (\x mx -> maybe x id mx) (l:ls) mlls' let lls' = zipWith (\x mx -> maybe x id mx) (l:ls) mlls'
return $ Just $ LayoutSelection lls' return $ Just $ Select lls'
where rls (x:xs) = xs ++ [x] where rls (x:xs) = xs ++ [x]
rls [] = [] rls [] = []
rls' = reverse . rls . reverse rls' = reverse . rls . reverse
j s zs = case partition (\z -> s == description z) zs of j s zs = case partition ((s ==) . description) zs of (xs,ys) -> xs++ys
(xs,ys) -> xs++ys
switchl f = do ml' <- handleMessage l (SomeMessage Hide)
return $ Just (LayoutSelection $ f $ fromMaybe l ml':ls)
-- otherwise, or if we don't understand the message, pass it along to the real
-- layout:
handleMessage (LayoutSelection (l:ls)) m
= do ml' <- handleMessage l m
return $ (\l' -> LayoutSelection (l':ls)) `fmap` ml'
-- Unless there is no layout...
handleMessage (LayoutSelection []) _ = return Nothing
description (LayoutSelection (x:_)) = description x switchl f = do ml' <- handleMessage l (SomeMessage Hide)
description _ = "default" return $ Just (Select $ f $ fromMaybe l ml':ls)
-- otherwise, or if we don't understand the message, pass it along to the real layout:
handleMessage (Select (l:ls)) m = do
ml' <- handleMessage l m
return $ (\l' -> Select (l':ls)) `fmap` ml'
-- Unless there is no layout...
handleMessage (Select []) _ = return Nothing
description (Select (x:_)) = description x
description _ = "default"
-- --
-- Builtin layout algorithms: -- Builtin layout algorithms:
-- --