aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Roledex.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/Roledex.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/Roledex.hs')
-rw-r--r--XMonad/Layout/Roledex.hs70
1 files changed, 70 insertions, 0 deletions
diff --git a/XMonad/Layout/Roledex.hs b/XMonad/Layout/Roledex.hs
new file mode 100644
index 0000000..0c4eb5f
--- /dev/null
+++ b/XMonad/Layout/Roledex.hs
@@ -0,0 +1,70 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.Roledex
+-- Copyright : (c) tim.thelion@gmail.com
+-- License : BSD
+--
+-- Maintainer : tim.thelion@gmail.com
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Screenshot : <http://www.timthelion.com/rolodex.png>
+--
+-- This is a completely pointless layout which acts like Microsoft's Flip 3D
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.Roledex (
+ -- * Usage
+ -- $usage
+ Roledex(Roledex)) where
+
+import XMonad
+import XMonad.Layouts
+import qualified XMonad.StackSet as W
+import Graphics.X11.Xlib
+import Data.Ratio
+
+-- $usage
+--
+-- > import XMonad.Layout.Roledex
+-- > layouts = [ Layout Roledex ]
+
+-- %import XMonad.Layout.Roledex
+-- %layout , Layout Roledex
+
+data Roledex a = Roledex deriving ( Show, Read )
+
+instance LayoutClass Roledex Window where
+ doLayout _ = roledexLayout
+
+roledexLayout :: Eq a => Rectangle -> W.Stack a -> X ([(a, Rectangle)], Maybe (Roledex a))
+roledexLayout sc ws = return ([(W.focus ws, mainPane)] ++
+ (zip ups tops) ++
+ (reverse (zip dns bottoms))
+ ,Nothing)
+ where ups = W.up ws
+ dns = W.down ws
+ c = length ups + length dns
+ rect = fst $ splitHorizontallyBy (2%3 :: Ratio Int) $ fst (splitVerticallyBy (2%3 :: Ratio Int) sc)
+ gw = div' (w - rw) (fromIntegral c)
+ where
+ (Rectangle _ _ w _) = sc
+ (Rectangle _ _ rw _) = rect
+ gh = div' (h - rh) (fromIntegral c)
+ where
+ (Rectangle _ _ _ h) = sc
+ (Rectangle _ _ _ rh) = rect
+ mainPane = mrect (gw * fromIntegral c) (gh * fromIntegral c) rect
+ mrect mx my (Rectangle x y w h) = Rectangle (x + (fromIntegral mx)) (y + (fromIntegral my)) w h
+ tops = map f $ cd c (length dns)
+ bottoms = map f $ [0..(length dns)]
+ f n = mrect (gw * (fromIntegral n)) (gh * (fromIntegral n)) rect
+ cd n m = if n > m
+ then (n - 1) : (cd (n-1) m)
+ else []
+
+div' :: Integral a => a -> a -> a
+div' _ 0 = 0
+div' n o = div n o