From 8fb6a10052cb504ff52c93da9f371204ec27ebb6 Mon Sep 17 00:00:00 2001 From: David Roundy Date: Thu, 1 Nov 2007 16:29:15 +0100 Subject: port Combo (dropping combo). darcs-hash:20071101152915-72aca-5a3140d71085d6b46483907a51ed449b26c06c5f.gz --- Combo.hs | 62 ++++++++------------------------------------------------------ 1 file changed, 8 insertions(+), 54 deletions(-) diff --git a/Combo.hs b/Combo.hs index f450e9f..f3797a0 100644 --- a/Combo.hs +++ b/Combo.hs @@ -17,7 +17,7 @@ module XMonadContrib.Combo ( -- * Usage -- $usage - combo, combineTwo, + combineTwo, CombineTwo ) where @@ -25,7 +25,6 @@ import Control.Arrow ( first ) import Data.List ( delete, intersect, (\\) ) import Data.Maybe ( isJust ) import XMonad -import Operations ( LayoutMessages(ReleaseResources,Hide) ) import StackSet ( integrate, Stack(..) ) import XMonadContrib.Invisible import XMonadContrib.WindowNavigation ( MoveWindowToWindow(..) ) @@ -39,26 +38,16 @@ import qualified StackSet as W ( differentiate ) -- -- and add something like -- --- > combo (TwoPane 0.03 0.5) [(Layout Full,1),(Layout $ tabbed shrinkText defaultTConf,1)] --- --- or alternatively --- -- > combineTwo (TwoPane 0.03 0.5) (tabbed shrinkText defaultTConf) (tabbed shrinkText defaultTConf) -- -- to your layouts. --- --- The first argument to combo is a layout that will divide the screen into --- one or more subscreens. The second argument is a list of layouts which --- will be used to lay out the contents of each of those subscreens. --- Paired with each of these layouts is an integer giving the number of --- windows this section should hold. This number is ignored for the last --- layout, which will hold any excess windows. --- combineTwo is a new simpler (and yet in some ways more powerful) layout --- combinator. It only allows the combination of two layouts, but has the --- advantage of allowing you to dynamically adjust the layout, in terms of --- the number of windows in each sublayout. To do this, use --- WindowNavigation, and add the following key bindings (or something similar): +-- combineTwo is a new simple layout combinator. It allows the combination +-- of two layouts using a third to split the screen between the two, but +-- has the advantage of allowing you to dynamically adjust the layout, in +-- terms of the number of windows in each sublayout. To do this, use +-- WindowNavigation, and add the following key bindings (or something +-- similar): -- , ((modMask .|. controlMask .|. shiftMask, xK_Right), sendMessage $ Move R) -- , ((modMask .|. controlMask .|. shiftMask, xK_Left), sendMessage $ Move L) @@ -74,7 +63,7 @@ import qualified StackSet as W ( differentiate ) -- reimelement the core of xmonad yourself. -- %import XMonadContrib.Combo --- %layout , combo (twoPane 0.03 0.5) [(full,1),(tabbed shrinkText defaultTConf,1)] +-- %layout , combineTwo (TwoPane 0.03 0.5) (tabbed shrinkText defaultTConf) (tabbed shrinkText defaultTConf) data CombineTwo l l1 l2 a = C2 [a] [a] (l ()) (l1 a) (l2 a) deriving (Read, Show) @@ -134,41 +123,6 @@ instance (LayoutClass l (), LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, description (C2 _ _ super l1 l2) = "combining "++ description l1 ++" and "++ description l2 ++" with "++ description super -combo :: (Eq a, Show a, Read a, ReadableLayout a, LayoutClass l (Layout a, Int)) - => (l (Layout a, Int)) -> [(Layout a, Int)] -> Combo l a -combo = Combo (I []) - -data Combo l a = Combo (Invisible [] a) (l (Layout a, Int)) [(Layout a, Int)] - deriving (Show, Read) - -instance (Eq a, ReadableLayout a, LayoutClass l (Layout a, Int)) - => LayoutClass (Combo l) a where - doLayout (Combo (I f) super origls) rinput s = arrange (integrate s) - where arrange [] = return ([], Just $ Combo (I []) super origls) - arrange [w] = return ([(w,rinput)], Just $ Combo (I [w]) super origls) - arrange origws = - do (lrs, msuper') <- runLayout super rinput (W.differentiate $ take (length origws) origls) - let super' = maybe super id msuper' - f' = focus s:delete (focus s) f - lwrs [] _ = [] - lwrs [((l,_),r)] ws = [((l,r),differentiate f' ws)] - lwrs (((l,n),r):xs) ws = ((l,r),differentiate f' $ take len1 ws) : lwrs xs (drop len1 ws) - where len1 = min n (length ws - length xs) - out <- mapM (uncurry $ uncurry runLayout) $ lwrs lrs origws - let origls' = zipWith foo (out++repeat ([],Nothing)) origls - foo (_, Nothing) x = x - foo (_, Just l') (_, n) = (l', n) - return (concat $ map fst out, Just $ Combo (I f') super' origls') - handleMessage (Combo (I f) super origls) m = - do mls <- broadcastPrivate m (map fst origls) - let mls' = (\x->zipWith first (map const x) origls) `fmap` mls - f' = case fromMessage m of - Just ReleaseResources -> [] - _ -> f - msuper <- broadcastPrivate m [super] - case msuper of - Just [super'] -> return $ Just $ Combo (I f') super' $ maybe origls id mls' - _ -> return $ Combo (I f') super `fmap` mls' differentiate :: Eq q => [q] -> [q] -> Maybe (Stack q) differentiate (z:zs) xs | z `elem` xs = Just $ Stack { focus=z -- cgit v1.2.3