aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/SimpleDecoration.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-01-25 16:21:06 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-01-25 16:21:06 +0100
commit4d4b97a565478edb6144501666e199954242955c (patch)
tree1c16e40336504c18a199a1bc95d69af0b4596745 /XMonad/Layout/SimpleDecoration.hs
parent6cb9fc74d97b5b7a0497c3b27c047435a8cbb0e1 (diff)
downloadXMonadContrib-4d4b97a565478edb6144501666e199954242955c.tar.gz
XMonadContrib-4d4b97a565478edb6144501666e199954242955c.tar.xz
XMonadContrib-4d4b97a565478edb6144501666e199954242955c.zip
Adde SimpleDecoration, a layout modifier to add simple decorations to windows in any layout
darcs-hash:20080125152106-32816-342b1ed0a63edfc2726db6b887e2a101d8b71f9b.gz
Diffstat (limited to 'XMonad/Layout/SimpleDecoration.hs')
-rw-r--r--XMonad/Layout/SimpleDecoration.hs69
1 files changed, 69 insertions, 0 deletions
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