added module X.L.TwoPanePersistent

updated CHANGES.md
This commit is contained in:
namo626
2018-06-21 22:16:14 -04:00
parent 9fcea6cb55
commit 913183463a
3 changed files with 109 additions and 2 deletions

View File

@@ -109,6 +109,14 @@
### New Modules
* `XMonad.Layout.TwoPanePersistent`
A layout that is like TwoPane but keeps track of the slave window that is
currently beside the master. In TwoPane, the default behavior when the master
is focused is to display the next window in the stack on the slave pane. This
is a problem when a different slave window is selected without changing the stack
order.
* `XMonad.Hooks.RefocusLast`
Provides log and event hooks that keep track of recently focused windows on
@@ -209,10 +217,10 @@
strategy with fewer quirks for tiled layouts using X.L.Spacing.
* `XMonad.Layout.Fullscreen`
The fullscreen layouts will now not render any window that is totally
obscured by fullscreen windows.
* `XMonad.Layout.Gaps`
Extended the sendMessage interface with `ModifyGaps` to allow arbitrary

View File

@@ -0,0 +1,98 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.TwoPanePersistent
-- Copyright : (c) Chayanon Wichitrnithed
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : Chayanon Wichitrnithed <namowi@gatech.edu>
-- Stability : unstable
-- Portability : unportable
--
-- This layout is the same as "XMonad.Layout.TwoPane" except that it keeps track of the slave window
-- that is alongside the master pane. In other words, it prevents the slave pane
-- from changing after the focus goes back to the master pane.
-----------------------------------------------------------------------------
module XMonad.Layout.TwoPanePersistent
(
-- * Usage
-- $usage
TwoPanePersistent(..)
) where
import XMonad.StackSet (focus, up, down, Stack, Stack(..))
import XMonad hiding (focus)
-- $usage
-- Import the module in @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.TwoPanePersistent
--
-- Then add the layout to the @layoutHook@:
--
-- > myLayout = TwoPanePersistent Nothing (3/100) (1/2) ||| Full ||| etc..
-- > main = xmonad def { layoutHook = myLayout }
data TwoPanePersistent a = TwoPanePersistent
{ slaveWin :: (Maybe a) -- ^ slave window; if 'Nothing' or not in the current workspace,
-- the window below the master will go into the slave pane
, dFrac :: Rational -- ^ shrink/expand size
, mFrac :: Rational -- ^ initial master size
} deriving (Show, Read)
instance (Show a, Eq a) => LayoutClass TwoPanePersistent a where
doLayout l r s =
case reverse (up s) of
-- master is focused
[] -> return $ focusedMaster l s r
-- slave is focused
(master:_) -> return $ focusedSlave l s r master
pureMessage (TwoPanePersistent w delta split) x =
case fromMessage x of
Just Shrink -> Just (TwoPanePersistent w delta (split - delta))
Just Expand -> Just (TwoPanePersistent w delta (split + delta))
_ -> Nothing
description _ = "TwoPanePersistent"
----------------------------------------------------------------------------------------
focusedMaster :: (Eq a) => TwoPanePersistent a -> Stack a -> Rectangle
-> ( [(a, Rectangle)], Maybe (TwoPanePersistent a) )
focusedMaster (TwoPanePersistent w delta split) s r =
let (left, right) = splitHorizontallyBy split r in
case down s of
-- there exist windows below the master
(next:_) -> let nextSlave = ( [(focus s, left), (next, right)]
, Just $ TwoPanePersistent (Just next) delta split )
in case w of
-- if retains state, preserve the layout
Just win -> if win `elem` (down s) && (focus s /= win)
then ( [(focus s, left), (win, right)]
, Just $ TwoPanePersistent w delta split )
else nextSlave
-- if no previous state, default to the next slave window
Nothing -> nextSlave
-- the master is the only window
[] -> ( [(focus s, r)]
, Just $ TwoPanePersistent Nothing delta split )
focusedSlave :: TwoPanePersistent a -> Stack a -> Rectangle -> a
-> ( [(a, Rectangle)], Maybe (TwoPanePersistent a) )
focusedSlave (TwoPanePersistent _ delta split) s r m =
( [(m, left), (focus s, right)]
, Just $ TwoPanePersistent (Just $ focus s) delta split )
where (left, right) = splitHorizontallyBy split r

View File

@@ -285,6 +285,7 @@ library
XMonad.Layout.ToggleLayouts
XMonad.Layout.TrackFloating
XMonad.Layout.TwoPane
XMonad.Layout.TwoPanePersistent
XMonad.Layout.WindowArranger
XMonad.Layout.WindowNavigation
XMonad.Layout.WindowSwitcherDecoration