aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/TilePrime.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
commit4866f2e367dfcf22a9591231ba40948826a1b438 (patch)
tree7a245caee3f146826b267d773b7eaa80386a818e /XMonad/Layout/TilePrime.hs
parent47589e1913fb9530481caedb543978a30d4323ea (diff)
downloadXMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.gz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.xz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.zip
Hierarchify
darcs-hash:20071101201059-a5988-fc1f1262bec1b69e13ba18ae7cefeafc8c4471d4.gz
Diffstat (limited to 'XMonad/Layout/TilePrime.hs')
-rw-r--r--XMonad/Layout/TilePrime.hs104
1 files changed, 104 insertions, 0 deletions
diff --git a/XMonad/Layout/TilePrime.hs b/XMonad/Layout/TilePrime.hs
new file mode 100644
index 0000000..36d54f6
--- /dev/null
+++ b/XMonad/Layout/TilePrime.hs
@@ -0,0 +1,104 @@
+{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances #-}
+-- --------------------------------------------------------------------------
+-- -- |
+-- -- Module : TilePrime.hs
+-- -- Copyright : (c) Eric Mertens 2007
+-- -- License : BSD3-style (see LICENSE)
+-- --
+-- -- Maintainer : emertens@gmail.com
+-- -- Stability : unstable
+-- -- Portability : not portable
+-- --
+-- -- TilePrime. Tile windows filling gaps created by resize hints
+-- --
+-- -----------------------------------------------------------------------------
+--
+
+module XMonad.Layout.TilePrime (
+ -- * Usage
+ -- $usage
+ TilePrime(TilePrime)
+ ) where
+
+import Control.Monad (mplus)
+import Data.List (mapAccumL)
+import Graphics.X11.Xlib
+import Graphics.X11.Xlib.Extras (getWMNormalHints)
+import XMonad.Operations
+import XMonad hiding (trace)
+import qualified XMonad.StackSet as W
+import {-#SOURCE#-} Config (borderWidth)
+
+-- $usage
+-- You can use this module with the following in your Config.hs file:
+--
+-- > import XMonad.Layout.TilePrime
+--
+-- and add the following line to your 'layouts'
+--
+-- > , Layout $ TilePrime nmaster delta ratio False
+--
+-- Use True as the last argument to get a wide layout.
+
+-- %import XMonad.Layout.TilePrime
+-- %layout , Layout $ TilePrime nmaster delta ratio False
+
+data TilePrime a = TilePrime
+ { nmaster :: Int
+ , delta, frac :: Rational
+ , flipped :: Bool
+ } deriving (Show, Read)
+
+instance LayoutClass TilePrime Window where
+ description c | flipped c = "TilePrime Horizontal"
+ | otherwise = "TilePrime Vertical"
+
+ pureMessage c m = fmap resize (fromMessage m) `mplus`
+ fmap incmastern (fromMessage m)
+ where
+ resize Shrink = c { frac = max 0 $ frac c - delta c }
+ resize Expand = c { frac = min 1 $ frac c + delta c }
+ incmastern (IncMasterN d) = c { nmaster = max 0 $ nmaster c + d }
+
+ doLayout TilePrime { frac = f, nmaster = m, flipped = flp } rect s = do
+ let xs = W.integrate s
+ hints <- withDisplay $ \ disp -> io (mapM (getWMNormalHints disp) xs)
+ let xs' = zip xs hints
+ (leftXs, rightXs) = splitAt m xs'
+ (leftRect, rightRect)
+ | null rightXs = (rect, Rectangle 0 0 0 0)
+ | null leftXs = (Rectangle 0 0 0 0, rect)
+ | flp = splitVerticallyBy f rect
+ | otherwise = splitHorizontallyBy f rect
+ masters = fillWindows leftRect leftXs
+ slaves = fillWindows rightRect rightXs
+ return (masters ++ slaves, Nothing)
+
+ where
+ fillWindows r xs = snd $ mapAccumL aux (r,n) xs
+ where n = fromIntegral (length xs) :: Rational
+
+ aux (r,n) (x,hint) = ((rest,n-1),(x,r'))
+ where
+ (allocated, _) | flp = splitHorizontallyBy (recip n) r
+ | otherwise = splitVerticallyBy (recip n) r
+
+ (w,h) = applySizeHints hint `underBorders` rect_D allocated
+
+ r' = r { rect_width = w, rect_height = h }
+
+ rest | flp = r { rect_x = rect_x r + toEnum (fromEnum w)
+ , rect_width = rect_width r - w }
+ | otherwise = r { rect_y = rect_y r + toEnum (fromEnum h)
+ , rect_height = rect_height r - h }
+
+rect_D :: Rectangle -> D
+rect_D Rectangle { rect_width = w, rect_height = h } = (w,h)
+
+-- | Transform a function on dimensions into one without regard for borders
+underBorders :: (D -> D) -> D -> D
+underBorders f = adjBorders 1 . f . adjBorders (-1)
+
+-- | Modify dimensions by a multiple of the current borders
+adjBorders :: Dimension -> D -> D
+adjBorders mult (w,h) = (w+2*mult*borderWidth, h+2*mult*borderWidth)