From 4d4b97a565478edb6144501666e199954242955c Mon Sep 17 00:00:00 2001
From: Andrea Rossato <andrea.rossato@unibz.it>
Date: Fri, 25 Jan 2008 16:21:06 +0100
Subject: Adde SimpleDecoration, a layout modifier to add simple decorations to
 windows in any layout

darcs-hash:20080125152106-32816-342b1ed0a63edfc2726db6b887e2a101d8b71f9b.gz
---
 XMonad/Layout/SimpleDecoration.hs | 69 +++++++++++++++++++++++++++++++++++++++
 xmonad-contrib.cabal              |  1 +
 2 files changed, 70 insertions(+)
 create mode 100644 XMonad/Layout/SimpleDecoration.hs

diff --git a/XMonad/Layout/SimpleDecoration.hs b/XMonad/Layout/SimpleDecoration.hs
new file mode 100644
index 0000000..f20cceb
--- /dev/null
+++ b/XMonad/Layout/SimpleDecoration.hs
@@ -0,0 +1,69 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Layout.SimpleDecoration
+-- Copyright   :  (c) 2007 Andrea Rossato
+-- License     :  BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer  :  andrea.rossato@unibz.it
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- A layout modifier for adding simple decorations to the windows of a
+-- given layout.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.SimpleDecoration
+    ( -- * Usage:
+      -- $usage
+      simpleDeco
+    , SimpleDecoration (..), defaultSimpleConfig
+    , shrinkText, CustomShrink(CustomShrink)
+    , Shrinker(..)
+    ) where
+
+import XMonad
+import XMonad.Layout.Decoration
+
+-- $usage
+-- You can use this module with the following in your
+-- @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.SimpleDecoration
+--
+-- Then edit your @layoutHook@ by adding the SimpleDecoration decoration to
+-- your layout:
+--
+-- > myL = simpleDeco shrinkText defaultSimpleConfig (layoutHook defaultConfig)
+-- > main = xmonad defaultConfig { layoutHook = myL }
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+--
+-- You can also edit the default configuration options.
+--
+-- > mySDConfig = defaultSimpleConfig { inactiveBorderColor = "red"
+-- >                                  , inactiveTextColor   = "red"}
+--
+-- and
+--
+-- > myL = dwmStyle shrinkText mySDConfig (layoutHook defaultConfig)
+
+-- | Add simple decorations to windows of a layout.
+simpleDeco :: Shrinker s => s -> DeConfig SimpleDecoration a
+           -> l a -> ModifiedLayout (Decoration SimpleDecoration s) l a
+simpleDeco s c = decoration s c
+
+defaultSimpleConfig :: DeConfig SimpleDecoration a
+defaultSimpleConfig = mkDefaultDeConfig $ Simple True
+
+data SimpleDecoration a = Simple Bool deriving (Show, Read)
+
+instance DecorationStyle SimpleDecoration a where
+    describeDeco _ = "Simple"
+    shrink (Simple b) (Rectangle _ _ _ dh) r@(Rectangle x y w h) =
+        if b then Rectangle x (y + fi dh) w (h - dh) else r
+    pureDecoration (Simple b) wh ht _ _ _ (_,Rectangle x y wid _) =
+        if b then Just $ Rectangle x y nwh ht else Just $ Rectangle x (y - fi ht) nwh ht
+            where nwh = min wid wh
\ No newline at end of file
diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal
index 3b217fb..7271aed 100644
--- a/xmonad-contrib.cabal
+++ b/xmonad-contrib.cabal
@@ -118,6 +118,7 @@ library
                         XMonad.Layout.ResizableTile
                         XMonad.Layout.Roledex
                         XMonad.Layout.Simplest
+                        XMonad.Layout.SimpleDecoration
                         XMonad.Layout.Spiral
                         XMonad.Layout.Square
                         XMonad.Layout.ShowWName
-- 
cgit v1.2.3