{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-}
module XMonad.Layout.SimpleFloat
(
simpleFloat
, simpleFloat'
, SimpleDecoration (..)
, SimpleFloat (..)
, shrinkText, CustomShrink(CustomShrink)
, Shrinker(..)
) where
import XMonad
import qualified XMonad.StackSet as S
import XMonad.Actions.MouseResize
import XMonad.Layout.Decoration
import XMonad.Layout.SimpleDecoration
import XMonad.Layout.WindowArranger
simpleFloat :: Eq a => ModifiedLayout (Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
simpleFloat :: forall a.
Eq a =>
ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat))
a
simpleFloat = DefaultShrinker
-> Theme
-> SimpleDecoration a
-> ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
-> ModifiedLayout
(Decoration SimpleDecoration DefaultShrinker)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat))
a
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def (Bool -> SimpleDecoration a
forall a. Bool -> SimpleDecoration a
Simple Bool
False) (ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat) a)
-> ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall a b. (a -> b) -> a -> b
$ SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrangeAll (SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a)
-> SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall a b. (a -> b) -> a -> b
$ Dimension -> SimpleFloat a
forall a. Dimension -> SimpleFloat a
SF Dimension
20)
simpleFloat' :: (Eq a, Shrinker s) => s -> Theme ->
ModifiedLayout (Decoration SimpleDecoration s)
(ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
simpleFloat' :: forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout
(Decoration SimpleDecoration s)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat))
a
simpleFloat' s
s Theme
c = s
-> Theme
-> SimpleDecoration a
-> ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
-> ModifiedLayout
(Decoration SimpleDecoration s)
(ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat))
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 (Bool -> SimpleDecoration a
forall a. Bool -> SimpleDecoration a
Simple Bool
False) (ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat) a)
-> ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall a b. (a -> b) -> a -> b
$ SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrangeAll (SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a)
-> SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall a b. (a -> b) -> a -> b
$ Dimension -> SimpleFloat a
forall a. Dimension -> SimpleFloat a
SF (Theme -> Dimension
decoHeight Theme
c))
newtype SimpleFloat a = SF Dimension deriving (Int -> SimpleFloat a -> ShowS
[SimpleFloat a] -> ShowS
SimpleFloat a -> String
(Int -> SimpleFloat a -> ShowS)
-> (SimpleFloat a -> String)
-> ([SimpleFloat a] -> ShowS)
-> Show (SimpleFloat a)
forall a. Int -> SimpleFloat a -> ShowS
forall a. [SimpleFloat a] -> ShowS
forall a. SimpleFloat a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleFloat a] -> ShowS
$cshowList :: forall a. [SimpleFloat a] -> ShowS
show :: SimpleFloat a -> String
$cshow :: forall a. SimpleFloat a -> String
showsPrec :: Int -> SimpleFloat a -> ShowS
$cshowsPrec :: forall a. Int -> SimpleFloat a -> ShowS
Show, ReadPrec [SimpleFloat a]
ReadPrec (SimpleFloat a)
Int -> ReadS (SimpleFloat a)
ReadS [SimpleFloat a]
(Int -> ReadS (SimpleFloat a))
-> ReadS [SimpleFloat a]
-> ReadPrec (SimpleFloat a)
-> ReadPrec [SimpleFloat a]
-> Read (SimpleFloat a)
forall a. ReadPrec [SimpleFloat a]
forall a. ReadPrec (SimpleFloat a)
forall a. Int -> ReadS (SimpleFloat a)
forall a. ReadS [SimpleFloat a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SimpleFloat a]
$creadListPrec :: forall a. ReadPrec [SimpleFloat a]
readPrec :: ReadPrec (SimpleFloat a)
$creadPrec :: forall a. ReadPrec (SimpleFloat a)
readList :: ReadS [SimpleFloat a]
$creadList :: forall a. ReadS [SimpleFloat a]
readsPrec :: Int -> ReadS (SimpleFloat a)
$creadsPrec :: forall a. Int -> ReadS (SimpleFloat a)
Read)
instance LayoutClass SimpleFloat Window where
description :: SimpleFloat Window -> String
description SimpleFloat Window
_ = String
"Float"
doLayout :: SimpleFloat Window
-> Rectangle
-> Stack Window
-> X ([(Window, Rectangle)], Maybe (SimpleFloat Window))
doLayout (SF Dimension
i) Rectangle
sc (S.Stack Window
w [Window]
l [Window]
r) = do
[(Window, Rectangle)]
wrs <- (Window -> X (Window, Rectangle))
-> [Window] -> X [(Window, Rectangle)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Dimension -> Rectangle -> Window -> X (Window, Rectangle)
getSize Dimension
i Rectangle
sc) (Window
w Window -> [Window] -> [Window]
forall a. a -> [a] -> [a]
: [Window] -> [Window]
forall a. [a] -> [a]
reverse [Window]
l [Window] -> [Window] -> [Window]
forall a. [a] -> [a] -> [a]
++ [Window]
r)
([(Window, Rectangle)], Maybe (SimpleFloat Window))
-> X ([(Window, Rectangle)], Maybe (SimpleFloat Window))
forall (m :: * -> *) a. Monad m => a -> m a
return ([(Window, Rectangle)]
wrs, Maybe (SimpleFloat Window)
forall a. Maybe a
Nothing)
getSize :: Dimension -> Rectangle -> Window -> X (Window,Rectangle)
getSize :: Dimension -> Rectangle -> Window -> X (Window, Rectangle)
getSize Dimension
i (Rectangle Position
rx Position
ry Dimension
_ Dimension
_) Window
w = do
Display
d <- (XConf -> Display) -> X Display
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Display
display
Dimension
bw <- (XConf -> Dimension) -> X Dimension
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (XConfig Layout -> Dimension
forall (l :: * -> *). XConfig l -> Dimension
borderWidth (XConfig Layout -> Dimension)
-> (XConf -> XConfig Layout) -> XConf -> Dimension
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config)
WindowAttributes
wa <- IO WindowAttributes -> X WindowAttributes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO WindowAttributes -> X WindowAttributes)
-> IO WindowAttributes -> X WindowAttributes
forall a b. (a -> b) -> a -> b
$ Display -> Window -> IO WindowAttributes
getWindowAttributes Display
d Window
w
let ny :: Position
ny = Position
ry Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi Dimension
i
x :: Position
x = Position -> Position -> Position
forall a. Ord a => a -> a -> a
max Position
rx (Position -> Position) -> Position -> Position
forall a b. (a -> b) -> a -> b
$ CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fi (CInt -> Position) -> CInt -> Position
forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_x WindowAttributes
wa
y :: Position
y = Position -> Position -> Position
forall a. Ord a => a -> a -> a
max Position
ny (Position -> Position) -> Position -> Position
forall a b. (a -> b) -> a -> b
$ CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fi (CInt -> Position) -> CInt -> Position
forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_y WindowAttributes
wa
wh :: Dimension
wh = CInt -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi (WindowAttributes -> CInt
wa_width WindowAttributes
wa) Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
+ (Dimension
bw Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
* Dimension
2)
ht :: Dimension
ht = CInt -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi (WindowAttributes -> CInt
wa_height WindowAttributes
wa) Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
+ (Dimension
bw Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
* Dimension
2)
(Window, Rectangle) -> X (Window, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Window
w, Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x Position
y Dimension
wh Dimension
ht)