aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/HintedGrid.hs
diff options
context:
space:
mode:
authorLukas Mai <l.mai@web.de>2008-09-30 16:17:15 +0200
committerLukas Mai <l.mai@web.de>2008-09-30 16:17:15 +0200
commit1ea0a9e0da9c29518b3e518b0a07ae21bac36cc8 (patch)
tree615c56a369527307175269290b06fe5b5e91117b /XMonad/Layout/HintedGrid.hs
parent3e16bf804b6f45b795b85cb64cb650273d317589 (diff)
downloadXMonadContrib-1ea0a9e0da9c29518b3e518b0a07ae21bac36cc8.tar.gz
XMonadContrib-1ea0a9e0da9c29518b3e518b0a07ae21bac36cc8.tar.xz
XMonadContrib-1ea0a9e0da9c29518b3e518b0a07ae21bac36cc8.zip
XMonad.Layout.HintedGrid: add GridRatio (--no-test because of haddock breakage)
darcs-hash:20080930141715-462cf-79a7ea8fc204d24b9cca37ab59ae71933d0d75b0.gz
Diffstat (limited to 'XMonad/Layout/HintedGrid.hs')
-rw-r--r--XMonad/Layout/HintedGrid.hs27
1 files changed, 18 insertions, 9 deletions
diff --git a/XMonad/Layout/HintedGrid.hs b/XMonad/Layout/HintedGrid.hs
index f8a52c3..c4317da 100644
--- a/XMonad/Layout/HintedGrid.hs
+++ b/XMonad/Layout/HintedGrid.hs
@@ -18,7 +18,7 @@
module XMonad.Layout.HintedGrid (
-- * Usage
-- $usage
- Grid(..), arrange
+ Grid(..), arrange, defaultRatio
) where
import Prelude hiding ((.))
@@ -44,16 +44,25 @@ infixr 9 .
-- > myLayouts = Grid False ||| Full ||| etc..
-- > main = xmonad defaultConfig { layoutHook = myLayouts }
--
+-- You can also specify an aspect ratio for Grid to strive for with the
+-- GridRatio constructor:
+--
+-- > myLayouts = GridRatio (4/3) False ||| etc.
+--
-- For more detailed instructions on editing the layoutHook see
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
-- | Automatic mirroring of hinted layouts doesn't work very well, so this
-- 'Grid' comes with built-in mirroring. @Grid False@ is the normal layout,
-- @Grid True@ is the mirrored variant (rotated by 90 degrees).
-data Grid a = Grid Bool deriving (Read, Show)
+data Grid a = Grid Bool | GridRatio Double Bool deriving (Read, Show)
+
+defaultRatio :: Double
+defaultRatio = 16/9
instance LayoutClass Grid Window where
- doLayout (Grid m) r w = flip (,) Nothing . arrange m r (integrate w)
+ doLayout (Grid m) r w = doLayout (GridRatio defaultRatio m) r w
+ doLayout (GridRatio d m) r w = flip (,) Nothing . arrange d m r (integrate w)
replicateS :: Int -> (a -> (b, a)) -> a -> ([b], a)
replicateS n = runState . replicateM n . State
@@ -92,12 +101,12 @@ doRect height = doR
zipWith3 (\x y (w, h) -> Rectangle (fromIntegral x) (fromIntegral y) w h) xs ys c' ++ doR width' (n - 1) cs
-- | The internal function for computing the grid layout.
-arrange :: Bool -> Rectangle -> [Window] -> X [(Window, Rectangle)]
-arrange mirror (Rectangle rx ry rw rh) wins = do
+arrange :: Double -> Bool -> Rectangle -> [Window] -> X [(Window, Rectangle)]
+arrange aspectRatio mirror (Rectangle rx ry rw rh) wins = do
proto <- mapM mkAdjust wins
let
adjs = map (\f -> twist . f . twist) proto
- rs = arrange' (twist (rw, rh)) adjs
+ rs = arrange' aspectRatio (twist (rw, rh)) adjs
rs' = map (\(Rectangle x y w h) -> uncurry (uncurry Rectangle (twist (x, y))) (twist (w, h))) rs
return . zip wins . map (\r -> r{ rect_x = rect_x r + rx, rect_y = rect_y r + ry }) $ rs'
where
@@ -105,11 +114,11 @@ arrange mirror (Rectangle rx ry rw rh) wins = do
| mirror = \(a, b) -> (b, a)
| otherwise = id
-arrange' :: D -> [D -> D] -> [Rectangle]
-arrange' (rw, rh) adjs = reverse $ doRect rh rw (fromIntegral ncolumns) (ecols ++ cols)
+arrange' :: Double -> D -> [D -> D] -> [Rectangle]
+arrange' aspectRatio (rw, rh) adjs = reverse $ doRect rh rw (fromIntegral ncolumns) (ecols ++ cols)
where
nwindows = length adjs
- ncolumns = max 1 . round . sqrt $ fromIntegral nwindows * 9 * fromIntegral rw / (16 * fromIntegral rh :: Double)
+ ncolumns = max 1 . round . sqrt $ fromIntegral nwindows * fromIntegral rw / (fromIntegral rh * aspectRatio)
nrows = nwindows `div` ncolumns
nextras = nwindows - ncolumns * nrows
(ecols, adjs') = replicateS nextras (splitAt (nrows + 1)) $ reverse adjs