aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--Accordion.hs21
1 files changed, 11 insertions, 10 deletions
diff --git a/Accordion.hs b/Accordion.hs
index 74c53b5..5bfd77f 100644
--- a/Accordion.hs
+++ b/Accordion.hs
@@ -15,14 +15,13 @@
module XMonadContrib.Accordion (
-- * Usage
-- $usage
- accordion) where
+ Accordion(Accordion)) where
import XMonad
import Operations
import qualified StackSet as W
import Graphics.X11.Xlib
import Data.Ratio
-import XMonadContrib.LayoutHelpers ( idModify )
-- $usage
-- > import XMonadContrib.Accordion
@@ -31,22 +30,24 @@ import XMonadContrib.LayoutHelpers ( idModify )
-- %import XMonadContrib.Accordion
-- %layout , accordion
-accordion :: Eq a => Layout a
-accordion = Layout { doLayout = accordionLayout, modifyLayout = idModify }
+data Accordion a = Accordion deriving ( Read, Show )
-accordionLayout :: Eq a => Rectangle -> W.Stack a -> X ([(a, Rectangle)], Maybe (Layout a))
+instance Layout Accordion Window where
+ doLayout _ = accordionLayout
+
+accordionLayout :: Eq a => Rectangle -> W.Stack a -> X ([(a, Rectangle)], Maybe (Accordion a))
accordionLayout sc ws = return ((zip ups tops) ++
[(W.focus ws, mainPane)] ++
(zip dns bottoms)
,Nothing)
where ups = W.up ws
dns = W.down ws
- (top, allButTop) = splitVerticallyBy (1%8) sc
- (center, bottom) = splitVerticallyBy (6%7) allButTop
- (allButBottom, _) = splitVerticallyBy (7%8) sc
+ (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 []
+ tops = if ups /= [] then splitVertically (length ups) top else []
+ bottoms = if dns /= [] then splitVertically (length dns) bottom else []