blob: 0c4eb5f5e4637b48af0d895344e59396c1c43f2e (
plain) (
blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
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
|