aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/DwmStyle.hs
blob: bef196f9bba98b1847fd042d31b056f31d1b3231 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
{-# 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
    , DeConfig (..)
    , 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