[xmonad] darcs patch: X.L.Master: Add FixMaster layout modifier
adam vogt
vogt.adam at gmail.com
Mon Dec 22 04:41:53 UTC 2014
Thanks Anton, I've applied your patch
On Fri, Dec 19, 2014 at 8:25 PM, Anton Vorontsov <anton at enomsg.org> wrote:
> 1 patch for repository http://code.haskell.org/XMonadContrib:
>
> Fri Dec 19 17:13:39 PST 2014 Anton Vorontsov <anton at enomsg.org>
> * X.L.Master: Add FixMaster layout modifier
>
> This layout modifier is useful for the case if you desire to add a master
> pane that has fixed width (it's fixed even if there is just one window
> opened). Especially nice feature if you don't want to have too wide
> terminal in a master pane.
>
> The layout is implemented as an addition to Master layout, so it reuses
> most of the code.
>
>
>
> [X.L.Master: Add FixMaster layout modifier
> Anton Vorontsov <anton at enomsg.org>**20141220011339
> Ignore-this: 82e9736853287f753248af41843ceb6b
>
> This layout modifier is useful for the case if you desire to add a master
> pane that has fixed width (it's fixed even if there is just one window
> opened). Especially nice feature if you don't want to have too wide
> terminal in a master pane.
>
> The layout is implemented as an addition to Master layout, so it reuses
> most of the code.
> ] {
> hunk ./XMonad/Layout/Master.hs 21
> -- $usage
>
> mastered,
> + fixMastered,
> multimastered,
> AddMaster,
> ) where
> hunk ./XMonad/Layout/Master.hs 29
> import XMonad
> import qualified XMonad.StackSet as S
> import XMonad.Layout.LayoutModifier
> +import Control.Monad
>
> -- $usage
> -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
> hunk ./XMonad/Layout/Master.hs 41
> --
> -- > mastered (1/100) (1/2) $ Grid
> --
> +-- Or if you prefer to have a master with fixed width:
> +--
> +-- > fixMastered (1/100) (1/2) $ Grid
> +--
> -- Or if you want multiple (here two) master windows from the beginning:
> --
> -- > multimastered 2 (1/100) (1/2) $ Grid
> hunk ./XMonad/Layout/Master.hs 62
> -- layout
> data AddMaster a = AddMaster Int Rational Rational deriving (Show, Read)
>
> --- | Modifier which converts given layout to a mastered one
> multimastered :: (LayoutClass l a) =>
> Int -- ^ @k@, number of master windows
> -> Rational -- ^ @delta@, the ratio of the screen to resize by
> hunk ./XMonad/Layout/Master.hs 78
> mastered delta frac = multimastered 1 delta frac
>
> instance LayoutModifier AddMaster Window where
> - modifyLayout (AddMaster k delta frac) = applyMaster k delta frac
> + modifyLayout (AddMaster k delta frac) = applyMaster False k delta frac
> modifierDescription _ = "Mastered"
>
> pureMess (AddMaster k delta frac) m
> hunk ./XMonad/Layout/Master.hs 88
>
> pureMess _ _ = Nothing
>
> +data FixMaster a = FixMaster (AddMaster a) deriving (Show, Read)
> +
> +instance LayoutModifier FixMaster Window where
> + modifyLayout (FixMaster (AddMaster k d f)) = applyMaster True k d f
> + modifierDescription (FixMaster a) = "Fix" ++ modifierDescription a
> + pureMess (FixMaster a) m = liftM FixMaster (pureMess a m)
> +
> +fixMastered :: (LayoutClass l a) =>
> + Rational -- ^ @delta@, the ratio of the screen to resize by
> + -> Rational -- ^ @frac@, what portion of the screen to use for the master window
> + -> l a -- ^ the layout to be modified
> + -> ModifiedLayout FixMaster l a
> +fixMastered delta frac = ModifiedLayout . FixMaster $ AddMaster 1 delta frac
> +
> -- | Internal function for adding a master window and let the modified
> -- layout handle the rest of the windows
> applyMaster :: (LayoutClass l Window) =>
> hunk ./XMonad/Layout/Master.hs 105
> - Int
> + Bool
> + -> Int
> -> Rational
> -> Rational
> -> S.Workspace WorkspaceId (l Window) Window
> hunk ./XMonad/Layout/Master.hs 112
> -> Rectangle
> -> X ([(Window, Rectangle)], Maybe (l Window))
> -applyMaster k _ frac wksp rect = do
> +applyMaster f k _ frac wksp rect = do
> let st= S.stack wksp
> let ws = S.integrate' $ st
> hunk ./XMonad/Layout/Master.hs 115
> - let n = length ws
> + let n = length ws + fromEnum f
> if n > 1 then do
> if(n<=k) then
> return ((divideCol rect ws), Nothing)
> }
>
>
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://www.haskell.org/mailman/listinfo/xmonad
>
More information about the xmonad
mailing list