{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.TwoPanePersistent
-- Description :  "XMonad.Layout.TwoPane" with a persistent stack window.
-- 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.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
  { forall a. TwoPanePersistent a -> Maybe a
slaveWin :: Maybe a  -- ^ slave window; if 'Nothing' or not in the current workspace,
                         -- the window below the master will go into the slave pane
  , forall a. TwoPanePersistent a -> Rational
dFrac :: Rational -- ^ shrink/expand size
  , forall a. TwoPanePersistent a -> Rational
mFrac :: Rational -- ^ initial master size
  } deriving (Int -> TwoPanePersistent a -> ShowS
forall a. Show a => Int -> TwoPanePersistent a -> ShowS
forall a. Show a => [TwoPanePersistent a] -> ShowS
forall a. Show a => TwoPanePersistent a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TwoPanePersistent a] -> ShowS
$cshowList :: forall a. Show a => [TwoPanePersistent a] -> ShowS
show :: TwoPanePersistent a -> String
$cshow :: forall a. Show a => TwoPanePersistent a -> String
showsPrec :: Int -> TwoPanePersistent a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> TwoPanePersistent a -> ShowS
Show, ReadPrec [TwoPanePersistent a]
ReadPrec (TwoPanePersistent a)
ReadS [TwoPanePersistent a]
forall a. Read a => ReadPrec [TwoPanePersistent a]
forall a. Read a => ReadPrec (TwoPanePersistent a)
forall a. Read a => Int -> ReadS (TwoPanePersistent a)
forall a. Read a => ReadS [TwoPanePersistent a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TwoPanePersistent a]
$creadListPrec :: forall a. Read a => ReadPrec [TwoPanePersistent a]
readPrec :: ReadPrec (TwoPanePersistent a)
$creadPrec :: forall a. Read a => ReadPrec (TwoPanePersistent a)
readList :: ReadS [TwoPanePersistent a]
$creadList :: forall a. Read a => ReadS [TwoPanePersistent a]
readsPrec :: Int -> ReadS (TwoPanePersistent a)
$creadsPrec :: forall a. Read a => Int -> ReadS (TwoPanePersistent a)
Read)


instance (Show a, Eq a) => LayoutClass TwoPanePersistent a where
  doLayout :: TwoPanePersistent a
-> Rectangle
-> Stack a
-> X ([(a, Rectangle)], Maybe (TwoPanePersistent a))
doLayout TwoPanePersistent a
l Rectangle
r Stack a
s =
    case forall a. [a] -> [a]
reverse (forall a. Stack a -> [a]
up Stack a
s) of
      -- master is focused
      []         -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Eq a =>
TwoPanePersistent a
-> Stack a
-> Rectangle
-> ([(a, Rectangle)], Maybe (TwoPanePersistent a))
focusedMaster TwoPanePersistent a
l Stack a
s Rectangle
r

      -- slave is focused
      (a
master:[a]
_) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
TwoPanePersistent a
-> Stack a
-> Rectangle
-> a
-> ([(a, Rectangle)], Maybe (TwoPanePersistent a))
focusedSlave TwoPanePersistent a
l Stack a
s Rectangle
r a
master


  pureMessage :: TwoPanePersistent a -> SomeMessage -> Maybe (TwoPanePersistent a)
pureMessage (TwoPanePersistent Maybe a
w Rational
delta Rational
split) SomeMessage
x =
    case forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
x of
      Just Resize
Shrink -> forall a. a -> Maybe a
Just (forall a. Maybe a -> Rational -> Rational -> TwoPanePersistent a
TwoPanePersistent Maybe a
w Rational
delta (forall a. Ord a => a -> a -> a
max Rational
0 (Rational
split forall a. Num a => a -> a -> a
- Rational
delta)))
      Just Resize
Expand -> forall a. a -> Maybe a
Just (forall a. Maybe a -> Rational -> Rational -> TwoPanePersistent a
TwoPanePersistent Maybe a
w Rational
delta (forall a. Ord a => a -> a -> a
min Rational
1 (Rational
split forall a. Num a => a -> a -> a
+ Rational
delta)))
      Maybe Resize
_ -> forall a. Maybe a
Nothing

  description :: TwoPanePersistent a -> String
description TwoPanePersistent a
_ = String
"TwoPanePersistent"


----------------------------------------------------------------------------------------

focusedMaster :: (Eq a) => TwoPanePersistent a -> Stack a -> Rectangle
              -> ( [(a, Rectangle)], Maybe (TwoPanePersistent a) )
focusedMaster :: forall a.
Eq a =>
TwoPanePersistent a
-> Stack a
-> Rectangle
-> ([(a, Rectangle)], Maybe (TwoPanePersistent a))
focusedMaster (TwoPanePersistent Maybe a
w Rational
delta Rational
split) Stack a
s Rectangle
r =
  let (Rectangle
left, Rectangle
right) = forall r. RealFrac r => r -> Rectangle -> (Rectangle, Rectangle)
splitHorizontallyBy Rational
split Rectangle
r in
      case forall a. Stack a -> [a]
down Stack a
s of
        -- there exist windows below the master
        (a
next:[a]
_) -> let nextSlave :: ([(a, Rectangle)], Maybe (TwoPanePersistent a))
nextSlave = ( [(forall a. Stack a -> a
focus Stack a
s, Rectangle
left), (a
next, Rectangle
right)]
                                    , forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> Rational -> Rational -> TwoPanePersistent a
TwoPanePersistent (forall a. a -> Maybe a
Just a
next) Rational
delta Rational
split )
                    in case Maybe a
w of
                      -- if retains state, preserve the layout
                      Just a
win -> if a
win forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` forall a. Stack a -> [a]
down Stack a
s Bool -> Bool -> Bool
&& (forall a. Stack a -> a
focus Stack a
s forall a. Eq a => a -> a -> Bool
/= a
win)
                                  then ( [(forall a. Stack a -> a
focus Stack a
s, Rectangle
left), (a
win, Rectangle
right)]
                                       , forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> Rational -> Rational -> TwoPanePersistent a
TwoPanePersistent Maybe a
w Rational
delta Rational
split )
                                  else ([(a, Rectangle)], Maybe (TwoPanePersistent a))
nextSlave
                      -- if no previous state, default to the next slave window
                      Maybe a
Nothing -> ([(a, Rectangle)], Maybe (TwoPanePersistent a))
nextSlave


        -- the master is the only window
        []       -> ( [(forall a. Stack a -> a
focus Stack a
s, Rectangle
r)]
                    , forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> Rational -> Rational -> TwoPanePersistent a
TwoPanePersistent forall a. Maybe a
Nothing Rational
delta Rational
split )



focusedSlave :: TwoPanePersistent a -> Stack a -> Rectangle -> a
             -> ( [(a, Rectangle)], Maybe (TwoPanePersistent a) )
focusedSlave :: forall a.
TwoPanePersistent a
-> Stack a
-> Rectangle
-> a
-> ([(a, Rectangle)], Maybe (TwoPanePersistent a))
focusedSlave (TwoPanePersistent Maybe a
_ Rational
delta Rational
split) Stack a
s Rectangle
r a
m =
  ( [(a
m, Rectangle
left), (forall a. Stack a -> a
focus Stack a
s, Rectangle
right)]
  , forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> Rational -> Rational -> TwoPanePersistent a
TwoPanePersistent (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Stack a -> a
focus Stack a
s) Rational
delta Rational
split )
  where (Rectangle
left, Rectangle
right) = forall r. RealFrac r => r -> Rectangle -> (Rectangle, Rectangle)
splitHorizontallyBy Rational
split Rectangle
r