{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
module XMonad.Layout.CenteredMaster (
centerMaster,
topRightMaster,
CenteredMaster, TopRightMaster,
) where
import XMonad
import XMonad.Layout.LayoutModifier
import qualified XMonad.StackSet as W
type Positioner = Rectangle -> Rectangle
data CenteredMaster a = CenteredMaster deriving (Read,Show)
instance LayoutModifier CenteredMaster Window where
modifyLayout CenteredMaster = applyPosition (center (5/7) (5/7))
data TopRightMaster a = TopRightMaster deriving (Read,Show)
instance LayoutModifier TopRightMaster Window where
modifyLayout TopRightMaster = applyPosition (topRight (3/7) (1/2))
centerMaster :: LayoutClass l a => l a -> ModifiedLayout CenteredMaster l a
centerMaster = ModifiedLayout CenteredMaster
topRightMaster :: LayoutClass l a => l a -> ModifiedLayout TopRightMaster l a
topRightMaster = ModifiedLayout TopRightMaster
applyPosition :: (LayoutClass l a, Eq a) =>
Positioner
-> W.Workspace WorkspaceId (l a) a
-> Rectangle
-> X ([(a, Rectangle)], Maybe (l a))
applyPosition pos wksp rect = do
let stack = W.stack wksp
let ws = W.integrate' $ stack
if null ws then
runLayout wksp rect
else do
let first = head ws
let other = tail ws
let filtStack = stack >>= W.filter (first /=)
wrs <- runLayout (wksp {W.stack = filtStack}) rect
return ((first, place pos other rect) : fst wrs, snd wrs)
place :: Positioner -> [a] -> Rectangle -> Rectangle
place _ [] rect = rect
place pos _ rect = pos rect
topRight :: Float -> Float -> Rectangle -> Rectangle
topRight rx ry (Rectangle sx sy sw sh) = Rectangle x sy w h
where w = round (fromIntegral sw * rx)
h = round (fromIntegral sh * ry)
x = sx + fromIntegral (sw-w)
center :: Float -> Float -> Rectangle -> Rectangle
center rx ry (Rectangle sx sy sw sh) = Rectangle x y w h
where w = round (fromIntegral sw * rx)
h = round (fromIntegral sh * ry)
x = sx + fromIntegral (sw-w) `div` 2
y = sy + fromIntegral (sh-h) `div` 2