{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.DwmStyle
-- Description :  A layout modifier for decorating windows in a dwm like style.
-- 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
    , Theme (..)
    , def
    , DwmStyle (..)
    , 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 def (layoutHook def)
-- > main = xmonad def { 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 = def { inactiveBorderColor = "red"
-- >                  , inactiveTextColor   = "red"}
--
-- and
--
-- > myL = dwmStyle shrinkText myDWConfig (layoutHook def)
--
-- A complete xmonad.hs file for this would therefore be:
--
-- > import XMonad
-- > import XMonad.Layout.DwmStyle
-- >
-- > main = xmonad def {
-- >     layoutHook = dwmStyle shrinkText def (layoutHook def)
-- >     }
--


-- | Add simple old dwm-style decorations to windows of a layout.
dwmStyle :: (Eq a, Shrinker s) => s -> Theme
         -> l a -> ModifiedLayout (Decoration DwmStyle s) l a
dwmStyle :: forall a s (l :: * -> *).
(Eq a, Shrinker s) =>
s -> Theme -> l a -> ModifiedLayout (Decoration DwmStyle s) l a
dwmStyle s
s Theme
c = s
-> Theme
-> DwmStyle a
-> l a
-> ModifiedLayout (Decoration DwmStyle s) l a
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
c DwmStyle a
forall a. DwmStyle a
Dwm

data DwmStyle a = Dwm deriving (Int -> DwmStyle a -> ShowS
[DwmStyle a] -> ShowS
DwmStyle a -> String
(Int -> DwmStyle a -> ShowS)
-> (DwmStyle a -> String)
-> ([DwmStyle a] -> ShowS)
-> Show (DwmStyle a)
forall a. Int -> DwmStyle a -> ShowS
forall a. [DwmStyle a] -> ShowS
forall a. DwmStyle a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DwmStyle a] -> ShowS
$cshowList :: forall a. [DwmStyle a] -> ShowS
show :: DwmStyle a -> String
$cshow :: forall a. DwmStyle a -> String
showsPrec :: Int -> DwmStyle a -> ShowS
$cshowsPrec :: forall a. Int -> DwmStyle a -> ShowS
Show, ReadPrec [DwmStyle a]
ReadPrec (DwmStyle a)
Int -> ReadS (DwmStyle a)
ReadS [DwmStyle a]
(Int -> ReadS (DwmStyle a))
-> ReadS [DwmStyle a]
-> ReadPrec (DwmStyle a)
-> ReadPrec [DwmStyle a]
-> Read (DwmStyle a)
forall a. ReadPrec [DwmStyle a]
forall a. ReadPrec (DwmStyle a)
forall a. Int -> ReadS (DwmStyle a)
forall a. ReadS [DwmStyle a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DwmStyle a]
$creadListPrec :: forall a. ReadPrec [DwmStyle a]
readPrec :: ReadPrec (DwmStyle a)
$creadPrec :: forall a. ReadPrec (DwmStyle a)
readList :: ReadS [DwmStyle a]
$creadList :: forall a. ReadS [DwmStyle a]
readsPrec :: Int -> ReadS (DwmStyle a)
$creadsPrec :: forall a. Int -> ReadS (DwmStyle a)
Read)

instance Eq a => DecorationStyle DwmStyle a where
    describeDeco :: DwmStyle a -> String
describeDeco DwmStyle a
_ = String
"DwmStyle"
    shrink :: DwmStyle a -> Rectangle -> Rectangle -> Rectangle
shrink  DwmStyle a
_ Rectangle
_  Rectangle
r = Rectangle
r
    pureDecoration :: DwmStyle a
-> Dimension
-> Dimension
-> Rectangle
-> Stack a
-> [(a, Rectangle)]
-> (a, Rectangle)
-> Maybe Rectangle
pureDecoration DwmStyle a
_ Dimension
wh Dimension
ht Rectangle
_ s :: Stack a
s@(Stack a
fw [a]
_ [a]
_) [(a, Rectangle)]
_ (a
w,Rectangle Position
x Position
y Dimension
wid Dimension
_) =
        if a
w a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
fw Bool -> Bool -> Bool
|| Bool -> Bool
not (Stack a -> a -> Bool
forall a. Eq a => Stack a -> a -> Bool
isInStack Stack a
s a
w) then Maybe Rectangle
forall a. Maybe a
Nothing else Rectangle -> Maybe Rectangle
forall a. a -> Maybe a
Just (Rectangle -> Maybe Rectangle) -> Rectangle -> Maybe Rectangle
forall a b. (a -> b) -> a -> b
$ Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi Dimension
nx) Position
y Dimension
nwh (Dimension -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi Dimension
ht)
            where nwh :: Dimension
nwh = Dimension -> Dimension -> Dimension
forall a. Ord a => a -> a -> a
min Dimension
wid (Dimension -> Dimension) -> Dimension -> Dimension
forall a b. (a -> b) -> a -> b
$ Dimension -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi Dimension
wh
                  nx :: Dimension
nx  = Position -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi Position
x Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
+ Dimension
wid Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
nwh