X.L.Master: turn it to a Layout modifier and update the code

This commit is contained in:
Ismael Carnales
2009-02-13 02:04:53 +00:00
parent 27bbeff92c
commit 3285ac8bb4

View File

@@ -1,110 +1,86 @@
{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances, FlexibleContexts #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances, FlexibleContexts, PatternGuards #-}
{-# LANGUAGE PatternGuards #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.Master -- Module : XMonad.Layout.Master
-- Copyright : (c) Lukas Mai -- Copyright : (c) Ismael Carnales, Lukas Mai
-- License : BSD-style (see LICENSE) -- License : BSD-style (see LICENSE)
-- --
-- Maintainer : <l.mai@web.de> -- Maintainer : Ismael Carnales <icarnales@gmail.com>
-- Stability : unstable -- Stability : unstable
-- Portability : unportable -- Portability : unportable
-- --
-- A layout that adds a distinguished master window to a base layout. -- Layout modfier that adds a master window to another layout.
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
module XMonad.Layout.Master ( module XMonad.Layout.Master (
-- * Usage -- * Usage
-- $usage -- $usage
mastered,
Master mastered
) where ) where
import XMonad import XMonad
import XMonad.StackSet import qualified XMonad.StackSet as S
import XMonad.Layout.LayoutModifier
import Data.List
import Data.Ord
-- $usage -- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- --
-- > import XMonad.Layout.Master -- > import XMonad.Layout.Master
-- --
-- and add something like -- Then edit your @layoutHook@ and add the Master modifier to the layout that
-- you prefer.
-- --
-- > mastered (1/100) (1/2) $ Grid -- > mastered (1/100) (1/2) $ Grid
-- --
-- to your layouts. This will use the left half of your screen for a master -- This will use the left half of your screen for a master window and let
-- window and let Grid manage the right half. -- Grid manage the right half.
-- --
-- For more detailed instructions on editing the layoutHook see -- For more detailed instructions on editing the layoutHook see
-- "XMonad.Doc.Extending#Editing_the_layout_hook". -- "XMonad.Doc.Extending#Editing_the_layout_hook".
-- --
-- Like 'XMonad.Layout.Tall', 'Master' supports the 'XMonad.Layout.Shrink' and -- Like 'XMonad.Layout.Tall', 'withMaster' supports the
-- 'XMonad.Layout.Expand' messages. -- 'XMonad.Layout.Shrink' and XMonad.Layout.Expand' messages.
mastered :: (LayoutClass l a) -- | Data type for LayoutModifier which converts given layout to a mastered
=> Rational -- ^ @delta@, the ratio of the screen to resize by -- layout
-> Rational -- ^ @frac@, what portion of the screen to reserve for the master window data AddMaster a = AddMaster Rational Rational deriving (Show, Read)
-> l a -- ^ the layout to use for the remaining windows
-> Master l a
mastered d f b = Master d f' b
where
f' = min 1 . max 0 $ f
data Master l a = -- | Modifier wich converts given layout to a mastered one
Master{ mastered :: (LayoutClass l a) =>
delta :: Rational, Rational -- ^ @delta@, the ratio of the screen to resize by
frac :: Rational, -> Rational -- ^ @frac@, what portion of the screen to use for the master window
base :: l a -> l a -- ^ the layout to be modified
} deriving (Show, Read, Eq, Ord) -> ModifiedLayout AddMaster l a
mastered delta frac = ModifiedLayout $ AddMaster delta frac
extractMaster :: Stack a -> (a, Maybe (Stack a)) instance LayoutModifier AddMaster Window where
extractMaster (Stack x ls rs) = case reverse ls of modifyLayout (AddMaster delta frac) = applyMaster delta frac
[] -> (x, differentiate rs) modifierDescription _ = "Mastered"
(m : ls') -> (m, Just $ Stack x (reverse ls') rs)
area :: Rectangle -> Dimension pureMess (AddMaster delta frac) m
area r = rect_width r * rect_height r | Just Shrink <- fromMessage m = Just $ AddMaster delta (frac-delta)
| Just Expand <- fromMessage m = Just $ AddMaster delta (frac+delta)
chop :: D -> Rectangle -> Rectangle pureMess _ _ = Nothing
chop (w, h) (Rectangle rx ry rw rh) =
let
r' = maximumBy (comparing area)
[ Rectangle rx (ry + fromIntegral h) rw (rh - h)
, Rectangle (rx + fromIntegral w) ry (rw - w) rh]
in
r'{ rect_width = max 0 $ rect_width r', rect_height = max 0 $ rect_height r' }
instance (LayoutClass l Window) => LayoutClass (Master l) Window where -- | Internal function for adding a master window and let the modified
description m = "Master " ++ description (base m) -- layout handle the rest of the windows
handleMessage m msg applyMaster :: (LayoutClass l Window) =>
| Just Shrink <- fromMessage msg = Rational
return . Just $ m{ frac = max 0 $ frac m - delta m } -> Rational
| Just Expand <- fromMessage msg = -> S.Workspace WorkspaceId (l Window) Window
return . Just $ m{ frac = min 1 $ frac m + delta m } -> Rectangle
| otherwise = -> X ([(Window, Rectangle)], Maybe (l Window))
fmap (fmap (\x -> m{ base = x })) $ handleMessage (base m) msg applyMaster _ frac wksp rect = do
runLayout ws rect = do let st= S.stack wksp
(f, ws', rect') <- case fmap extractMaster $ stack ws of let ws = S.integrate' $ st
Nothing -> if length ws > 2 then do
return (id, ws, rect) let m = head ws
Just (x, Nothing) -> do let (mr, sr) = splitHorizontallyBy frac rect
f <- mkAdjust x let nst = st>>= S.filter (m/=)
let wrs <- runLayout (wksp {S.stack = nst}) sr
(w', h') = f (rect_width rect, rect_height rect) return ((m, mr) : fst wrs, snd wrs)
xr = rect{ rect_width = w', rect_height = h' }
return (((x, xr) :), ws{ stack = Nothing }, Rectangle (rect_x xr + fromIntegral w') (rect_y xr) 0 0) else runLayout wksp rect
Just (x, Just st) -> do
f <- mkAdjust x
let
d@(w', h') = f (scale $ rect_width rect, rect_height rect)
xr = rect{ rect_width = w', rect_height = h' }
return (((x, xr) :), ws{ stack = Just st }, chop d rect)
(y, l) <- runLayout ws'{ layout = base m } rect'
return (f y, fmap (\x -> m{ base = x }) l)
where
m = layout ws
scale = round . (* frac m) . fromIntegral