{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module XMonad.Layout.SimpleDecoration
(
simpleDeco
, Theme (..)
, def
, SimpleDecoration (..)
, shrinkText, CustomShrink(CustomShrink)
, Shrinker(..)
) where
import XMonad
import XMonad.Layout.Decoration
simpleDeco :: (Eq a, Shrinker s) => s -> Theme
-> l a -> ModifiedLayout (Decoration SimpleDecoration s) l a
simpleDeco :: forall a s (l :: * -> *).
(Eq a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration SimpleDecoration s) l a
simpleDeco s
s Theme
c = s
-> Theme
-> SimpleDecoration a
-> l a
-> ModifiedLayout (Decoration SimpleDecoration 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 (SimpleDecoration a
-> l a -> ModifiedLayout (Decoration SimpleDecoration s) l a)
-> SimpleDecoration a
-> l a
-> ModifiedLayout (Decoration SimpleDecoration s) l a
forall a b. (a -> b) -> a -> b
$ Bool -> SimpleDecoration a
forall a. Bool -> SimpleDecoration a
Simple Bool
True
newtype SimpleDecoration a = Simple Bool deriving (Int -> SimpleDecoration a -> ShowS
[SimpleDecoration a] -> ShowS
SimpleDecoration a -> String
(Int -> SimpleDecoration a -> ShowS)
-> (SimpleDecoration a -> String)
-> ([SimpleDecoration a] -> ShowS)
-> Show (SimpleDecoration a)
forall a. Int -> SimpleDecoration a -> ShowS
forall a. [SimpleDecoration a] -> ShowS
forall a. SimpleDecoration a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleDecoration a] -> ShowS
$cshowList :: forall a. [SimpleDecoration a] -> ShowS
show :: SimpleDecoration a -> String
$cshow :: forall a. SimpleDecoration a -> String
showsPrec :: Int -> SimpleDecoration a -> ShowS
$cshowsPrec :: forall a. Int -> SimpleDecoration a -> ShowS
Show, ReadPrec [SimpleDecoration a]
ReadPrec (SimpleDecoration a)
Int -> ReadS (SimpleDecoration a)
ReadS [SimpleDecoration a]
(Int -> ReadS (SimpleDecoration a))
-> ReadS [SimpleDecoration a]
-> ReadPrec (SimpleDecoration a)
-> ReadPrec [SimpleDecoration a]
-> Read (SimpleDecoration a)
forall a. ReadPrec [SimpleDecoration a]
forall a. ReadPrec (SimpleDecoration a)
forall a. Int -> ReadS (SimpleDecoration a)
forall a. ReadS [SimpleDecoration a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SimpleDecoration a]
$creadListPrec :: forall a. ReadPrec [SimpleDecoration a]
readPrec :: ReadPrec (SimpleDecoration a)
$creadPrec :: forall a. ReadPrec (SimpleDecoration a)
readList :: ReadS [SimpleDecoration a]
$creadList :: forall a. ReadS [SimpleDecoration a]
readsPrec :: Int -> ReadS (SimpleDecoration a)
$creadsPrec :: forall a. Int -> ReadS (SimpleDecoration a)
Read)
instance Eq a => DecorationStyle SimpleDecoration a where
describeDeco :: SimpleDecoration a -> String
describeDeco SimpleDecoration a
_ = String
"Simple"
shrink :: SimpleDecoration a -> Rectangle -> Rectangle -> Rectangle
shrink (Simple Bool
b) (Rectangle Position
_ Position
_ Dimension
_ Dimension
dh) r :: Rectangle
r@(Rectangle Position
x Position
y Dimension
w Dimension
h) =
if Bool
b then Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x (Position
y Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi Dimension
dh) Dimension
w (Dimension
h Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
dh) else Rectangle
r
pureDecoration :: SimpleDecoration a
-> Dimension
-> Dimension
-> Rectangle
-> Stack a
-> [(a, Rectangle)]
-> (a, Rectangle)
-> Maybe Rectangle
pureDecoration (Simple Bool
b) Dimension
wh Dimension
ht Rectangle
_ Stack a
s [(a, Rectangle)]
_ (a
w,Rectangle Position
x Position
y Dimension
wid Dimension
_) =
if Stack a -> a -> Bool
forall a. Eq a => Stack a -> a -> Bool
isInStack Stack a
s a
w
then if Bool
b
then 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 Position
x Position
y Dimension
nwh Dimension
ht
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 Position
x (Position
y Position -> Position -> Position
forall a. Num a => a -> a -> a
- Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi Dimension
ht) Dimension
nwh Dimension
ht
else Maybe Rectangle
forall a. Maybe a
Nothing
where nwh :: Dimension
nwh = Dimension -> Dimension -> Dimension
forall a. Ord a => a -> a -> a
min Dimension
wid Dimension
wh