aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Accordion.hs
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Layout/Accordion.hs')
-rw-r--r--XMonad/Layout/Accordion.hs50
1 files changed, 50 insertions, 0 deletions
diff --git a/XMonad/Layout/Accordion.hs b/XMonad/Layout/Accordion.hs
new file mode 100644
index 0000000..f844c22
--- /dev/null
+++ b/XMonad/Layout/Accordion.hs
@@ -0,0 +1,50 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.Accordion
+-- Copyright : (c) glasser@mit.edu
+-- License : BSD
+--
+-- Maintainer : glasser@mit.edu
+-- Stability : unstable
+-- Portability : unportable
+--
+-- LayoutClass that puts non-focused windows in ribbons at the top and bottom
+-- of the screen.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.Accordion (
+ -- * Usage
+ -- $usage
+ Accordion(Accordion)) where
+
+import XMonad
+import XMonad.Layouts
+import qualified XMonad.StackSet as W
+import Graphics.X11.Xlib
+import Data.Ratio
+
+-- $usage
+-- > import XMonad.Layout.Accordion
+-- > layouts = [ Layout Accordion ]
+
+-- %import XMonad.Layout.Accordion
+-- %layout , Layout Accordion
+
+data Accordion a = Accordion deriving ( Read, Show )
+
+instance LayoutClass Accordion Window where
+ pureLayout _ sc ws = zip ups tops ++ [(W.focus ws, mainPane)] ++ zip dns bottoms
+ where
+ ups = W.up ws
+ dns = W.down ws
+ (top, allButTop) = splitVerticallyBy (1%8 :: Ratio Int) sc
+ (center, bottom) = splitVerticallyBy (6%7 :: Ratio Int) allButTop
+ (allButBottom, _) = splitVerticallyBy (7%8 :: Ratio Int) sc
+ mainPane | ups /= [] && dns /= [] = center
+ | ups /= [] = allButTop
+ | dns /= [] = allButBottom
+ | otherwise = sc
+ tops = if ups /= [] then splitVertically (length ups) top else []
+ bottoms = if dns /= [] then splitVertically (length dns) bottom else []