diff options
author | Andrea Rossato <andrea.rossato@unibz.it> | 2008-01-25 16:21:52 +0100 |
---|---|---|
committer | Andrea Rossato <andrea.rossato@unibz.it> | 2008-01-25 16:21:52 +0100 |
commit | fc912645dbc3e4915fb41f45846ff11b68909ef7 (patch) | |
tree | 5ed346162f8e6e5a0d19a0007dbca0bf78bcd953 /XMonad | |
parent | 4d4b97a565478edb6144501666e199954242955c (diff) | |
download | XMonadContrib-fc912645dbc3e4915fb41f45846ff11b68909ef7.tar.gz XMonadContrib-fc912645dbc3e4915fb41f45846ff11b68909ef7.tar.xz XMonadContrib-fc912645dbc3e4915fb41f45846ff11b68909ef7.zip |
Add DwmStyle, a layout modifier to add dwm-style decorations to windows in any layout
darcs-hash:20080125152152-32816-0480e941cb549521e145d7b02c8d44807f928ccb.gz
Diffstat (limited to 'XMonad')
-rw-r--r-- | XMonad/Layout/DwmStyle.hs | 69 |
1 files changed, 69 insertions, 0 deletions
diff --git a/XMonad/Layout/DwmStyle.hs b/XMonad/Layout/DwmStyle.hs new file mode 100644 index 0000000..787f656 --- /dev/null +++ b/XMonad/Layout/DwmStyle.hs @@ -0,0 +1,69 @@ +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Layout.DwmStyle +-- Copyright : (c) 2007 Andrea Rossato +-- License : BSD-style (see xmonad/LICENSE) +-- +-- Maintainer : andrea.rossato@unibz.it +-- Stability : unstable +-- Portability : unportable +-- +-- A layout modifier for decorating windows in a dwm like style. +----------------------------------------------------------------------------- + +module XMonad.Layout.DwmStyle + ( -- * Usage: + -- $usage + dwmStyle + , DwmStyle (..), defaultDwmStyleConfig + , shrinkText, CustomShrink(CustomShrink) + , Shrinker(..) + ) where + +import XMonad +import XMonad.StackSet ( Stack (..) ) +import XMonad.Layout.Decoration + +-- $usage +-- You can use this module with the following in your +-- @~\/.xmonad\/xmonad.hs@: +-- +-- > import XMonad.Layout.DwmStyle +-- +-- Then edit your @layoutHook@ by adding the DwmStyle decoration to +-- your layout: +-- +-- > myL = dwmStyle shrinkText defaultDwmStyleConfig (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. +-- +-- > myDWConfig = defaultDwmStyleConfig { inactiveBorderColor = "red" +-- > , inactiveTextColor = "red"} +-- +-- and +-- +-- > myL = dwmStyle shrinkText myDWConfig (layoutHook defaultConfig) + +-- | Add simple old dwm-style decorations to windows of a layout. +dwmStyle :: (Eq a, Shrinker s) => s -> DeConfig DwmStyle a + -> l a -> ModifiedLayout (Decoration DwmStyle s) l a +dwmStyle s c = decoration s c + +defaultDwmStyleConfig :: Eq a => DeConfig DwmStyle a +defaultDwmStyleConfig= mkDefaultDeConfig Dwm + +data DwmStyle a = Dwm deriving (Show, Read) + +instance Eq a => DecorationStyle DwmStyle a where + describeDeco _ = "DwmStyle" + shrink _ _ r = r + pureDecoration _ wh ht _ (Stack fw _ _) _ (win,Rectangle x y wid _) = + if win == fw then Nothing else Just $ Rectangle (fi nx) y nwh (fi ht) + where nwh = min wid $ fi wh + nx = fi x + wid - nwh |