aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Square.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/Square.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/Square.hs')
-rw-r--r--XMonad/Layout/Square.hs56
1 files changed, 56 insertions, 0 deletions
diff --git a/XMonad/Layout/Square.hs b/XMonad/Layout/Square.hs
new file mode 100644
index 0000000..e05f549
--- /dev/null
+++ b/XMonad/Layout/Square.hs
@@ -0,0 +1,56 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.Square
+-- Copyright : (c) David Roundy <droundy@darcs.net>
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : David Roundy <droundy@darcs.net>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A layout that splits the screen into a square area and the rest of the
+-- screen.
+-- This is probably only ever useful in combination with
+-- "XMonad.Layout.Combo".
+-- It sticks one window in a square region, and makes the rest
+-- of the windows live with what's left (in a full-screen sense).
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.Square (
+ -- * Usage
+ -- $usage
+ Square(..) ) where
+
+import XMonad
+import Graphics.X11.Xlib
+import XMonad.StackSet ( integrate )
+
+-- $usage
+-- You can use this module with the following in your Config.hs file:
+--
+-- > import XMonad.Layout.Square
+--
+-- An example layout using square together with "XMonad.Layout.Combo"
+-- to make the very last area square:
+--
+-- > , combo (combo (mirror $ twoPane 0.03 0.85),1)] (twoPane 0.03 0.5) )
+-- > [(twoPane 0.03 0.2,1),(combo [(twoPane 0.03 0.8,1),(square,1)]
+-- > [(tabbed,3),(tabbed,30),(tabbed,1),(tabbed,1)]
+
+-- %import XMonad.Layout.Square
+
+data Square a = Square deriving ( Read, Show )
+
+instance LayoutClass Square a where
+ pureLayout Square r s = arrange (integrate s)
+ where arrange ws@(_:_) = map (\w->(w,rest)) (init ws) ++ [(last ws,sq)]
+ arrange [] = [] -- actually, this is an impossible case
+ (rest, sq) = splitSquare r
+
+splitSquare :: Rectangle -> (Rectangle, Rectangle)
+splitSquare (Rectangle x y w h)
+ | w > h = (Rectangle x y (w - h) h, Rectangle (x+fromIntegral (w-h)) y h h)
+ | otherwise = (Rectangle x y w (h-w), Rectangle x (y+fromIntegral (h-w)) w w)