{-# OPTIONS_GHC -fglasgow-exts #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.Magnifier -- Copyright : (c) Peter De Wachter 2007 -- License : BSD-style (see xmonad/LICENSE) -- -- Maintainer : Peter De Wachter -- Stability : unstable -- Portability : unportable -- -- Screenshot : -- -- This layout hack increases the size of the window that has focus. -- ----------------------------------------------------------------------------- module XMonad.Layout.Magnifier ( -- * Usage -- $usage magnifier, Magnifier(..), Magnifier'(..)) where import Graphics.X11.Xlib (Window, Rectangle(..)) import XMonad import XMonad.StackSet import XMonad.Layout.LayoutModifier -- $usage -- > import XMonad.Layout.Magnifier -- > layouts = [ magnifier tiled , magnifier $ mirror tiled ] -- %import XMonad.Layout.Magnifier -- %layout , magnifier tiled -- %layout , magnifier $ mirror tiled -- | Increase the size of the window that has focus, unless it is the master window. data Magnifier a = Magnifier deriving (Read, Show) instance LayoutModifier Magnifier Window where modifierDescription _ = "Magnifier" redoLayout _ = unlessMaster applyMagnifier -- | Increase the size of the window that has focus, even if it is the master window. data Magnifier' a = Magnifier' deriving (Read, Show) instance LayoutModifier Magnifier' Window where modifierDescription _ = "Magnifier'" redoLayout _ = applyMagnifier magnifier :: l a -> ModifiedLayout Magnifier l a magnifier = ModifiedLayout Magnifier unlessMaster :: forall t t1 a a1 (m :: * -> *). (Monad m) => (t -> Stack a -> t1 -> m (t1, Maybe a1)) -> t -> Stack a -> t1 -> m (t1, Maybe a1) unlessMaster mainmod r s wrs = if null (up s) then return (wrs, Nothing) else mainmod r s wrs applyMagnifier :: Rectangle -> t -> [(Window, Rectangle)] -> X ([(Window, Rectangle)], Maybe a) applyMagnifier r _ wrs = do focused <- withWindowSet (return . peek) let mag (w,wr) ws | focused == Just w = ws ++ [(w, shrink r $ magnify wr)] | otherwise = (w,wr) : ws return (reverse $ foldr mag [] wrs, Nothing) magnify :: Rectangle -> Rectangle magnify (Rectangle x y w h) = Rectangle x' y' w' h' where x' = x - fromIntegral (w' - w) `div` 2 y' = y - fromIntegral (h' - h) `div` 2 w' = round $ fromIntegral w * zoom h' = round $ fromIntegral h * zoom zoom = 1.5 :: Double shrink :: Rectangle -> Rectangle -> Rectangle shrink (Rectangle sx sy sw sh) (Rectangle x y w h) = Rectangle x' y' w' h' where x' = max sx x y' = max sy y w' = min w (fromIntegral sx + sw - fromIntegral x') h' = min h (fromIntegral sy + sh - fromIntegral y')