{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module XMonad.Layout.OneBig (
OneBig (..)
) where
import XMonad
import qualified XMonad.StackSet as W
data OneBig a = OneBig Float Float deriving (ReadPrec [OneBig a]
ReadPrec (OneBig a)
Int -> ReadS (OneBig a)
ReadS [OneBig a]
(Int -> ReadS (OneBig a))
-> ReadS [OneBig a]
-> ReadPrec (OneBig a)
-> ReadPrec [OneBig a]
-> Read (OneBig a)
forall a. ReadPrec [OneBig a]
forall a. ReadPrec (OneBig a)
forall a. Int -> ReadS (OneBig a)
forall a. ReadS [OneBig a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OneBig a]
$creadListPrec :: forall a. ReadPrec [OneBig a]
readPrec :: ReadPrec (OneBig a)
$creadPrec :: forall a. ReadPrec (OneBig a)
readList :: ReadS [OneBig a]
$creadList :: forall a. ReadS [OneBig a]
readsPrec :: Int -> ReadS (OneBig a)
$creadsPrec :: forall a. Int -> ReadS (OneBig a)
Read,Int -> OneBig a -> ShowS
[OneBig a] -> ShowS
OneBig a -> String
(Int -> OneBig a -> ShowS)
-> (OneBig a -> String) -> ([OneBig a] -> ShowS) -> Show (OneBig a)
forall a. Int -> OneBig a -> ShowS
forall a. [OneBig a] -> ShowS
forall a. OneBig a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OneBig a] -> ShowS
$cshowList :: forall a. [OneBig a] -> ShowS
show :: OneBig a -> String
$cshow :: forall a. OneBig a -> String
showsPrec :: Int -> OneBig a -> ShowS
$cshowsPrec :: forall a. Int -> OneBig a -> ShowS
Show)
instance LayoutClass OneBig a where
pureLayout :: OneBig a -> Rectangle -> Stack a -> [(a, Rectangle)]
pureLayout = OneBig a -> Rectangle -> Stack a -> [(a, Rectangle)]
forall a. OneBig a -> Rectangle -> Stack a -> [(a, Rectangle)]
oneBigLayout
pureMessage :: OneBig a -> SomeMessage -> Maybe (OneBig a)
pureMessage = OneBig a -> SomeMessage -> Maybe (OneBig a)
forall a. OneBig a -> SomeMessage -> Maybe (OneBig a)
oneBigMessage
oneBigMessage :: OneBig a -> SomeMessage -> Maybe (OneBig a)
oneBigMessage :: forall a. OneBig a -> SomeMessage -> Maybe (OneBig a)
oneBigMessage (OneBig Float
cx Float
cy) SomeMessage
m = (Resize -> OneBig a) -> Maybe Resize -> Maybe (OneBig a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Resize -> OneBig a
forall {a}. Resize -> OneBig a
resize (SomeMessage -> Maybe Resize
forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
m)
where resize :: Resize -> OneBig a
resize Resize
Shrink = Float -> Float -> OneBig a
forall a. Float -> Float -> OneBig a
OneBig (Float
cxFloat -> Float -> Float
forall a. Num a => a -> a -> a
-Float
delta) (Float
cyFloat -> Float -> Float
forall a. Num a => a -> a -> a
-Float
delta)
resize Resize
Expand = Float -> Float -> OneBig a
forall a. Float -> Float -> OneBig a
OneBig (Float
cxFloat -> Float -> Float
forall a. Num a => a -> a -> a
+Float
delta) (Float
cyFloat -> Float -> Float
forall a. Num a => a -> a -> a
+Float
delta)
delta :: Float
delta = Float
3Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/Float
100
oneBigLayout :: OneBig a -> Rectangle -> W.Stack a -> [(a, Rectangle)]
oneBigLayout :: forall a. OneBig a -> Rectangle -> Stack a -> [(a, Rectangle)]
oneBigLayout (OneBig Float
cx Float
cy) Rectangle
rect Stack a
stack = [(a
master,Rectangle
masterRect)]
[(a, Rectangle)] -> [(a, Rectangle)] -> [(a, Rectangle)]
forall a. [a] -> [a] -> [a]
++ Rectangle -> [a] -> [(a, Rectangle)]
forall a. Rectangle -> [a] -> [(a, Rectangle)]
divideBottom Rectangle
bottomRect [a]
bottomWs
[(a, Rectangle)] -> [(a, Rectangle)] -> [(a, Rectangle)]
forall a. [a] -> [a] -> [a]
++ Rectangle -> [a] -> [(a, Rectangle)]
forall a. Rectangle -> [a] -> [(a, Rectangle)]
divideRight Rectangle
rightRect [a]
rightWs
where ws :: [a]
ws = Stack a -> [a]
forall a. Stack a -> [a]
W.integrate Stack a
stack
n :: Int
n = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
ws
ht :: Rectangle -> Dimension
ht (Rectangle Position
_ Position
_ Dimension
_ Dimension
hh) = Dimension
hh
wd :: Rectangle -> Dimension
wd (Rectangle Position
_ Position
_ Dimension
ww Dimension
_) = Dimension
ww
h' :: Dimension
h' = Float -> Dimension
forall a b. (RealFrac a, Integral b) => a -> b
round (Dimension -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Rectangle -> Dimension
ht Rectangle
rect)Float -> Float -> Float
forall a. Num a => a -> a -> a
*Float
cy)
w :: Dimension
w = Rectangle -> Dimension
wd Rectangle
rect
m :: Int
m = Int -> Dimension -> Dimension -> Int
calcBottomWs Int
n Dimension
w Dimension
h'
master :: a
master = [a] -> a
forall a. [a] -> a
head [a]
ws
other :: [a]
other = [a] -> [a]
forall a. [a] -> [a]
tail [a]
ws
bottomWs :: [a]
bottomWs = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
m [a]
other
rightWs :: [a]
rightWs = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
m [a]
other
masterRect :: Rectangle
masterRect = Int -> Int -> Float -> Float -> Rectangle -> Rectangle
cmaster Int
n Int
m Float
cx Float
cy Rectangle
rect
bottomRect :: Rectangle
bottomRect = Float -> Rectangle -> Rectangle
cbottom Float
cy Rectangle
rect
rightRect :: Rectangle
rightRect = Float -> Float -> Rectangle -> Rectangle
cright Float
cx Float
cy Rectangle
rect
calcBottomWs :: Int -> Dimension -> Dimension -> Int
calcBottomWs :: Int -> Dimension -> Dimension -> Int
calcBottomWs Int
n Dimension
w Dimension
h' = case Int
n of
Int
1 -> Int
0
Int
2 -> Int
1
Int
3 -> Int
2
Int
4 -> Int
2
Int
_ -> Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
wInt -> Int -> Int
forall a. Num a => a -> a -> a
*(Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Dimension
h'Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
+Dimension -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
w)
cmaster:: Int -> Int -> Float -> Float -> Rectangle -> Rectangle
cmaster :: Int -> Int -> Float -> Float -> Rectangle -> Rectangle
cmaster Int
n Int
m Float
cx Float
cy (Rectangle Position
x Position
y Dimension
sw Dimension
sh) = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x Position
y Dimension
w Dimension
h
where w :: Dimension
w = if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1 then
Float -> Dimension
forall a b. (RealFrac a, Integral b) => a -> b
round (Dimension -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
swFloat -> Float -> Float
forall a. Num a => a -> a -> a
*Float
cx)
else
Dimension
sw
h :: Dimension
h = if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 then
Float -> Dimension
forall a b. (RealFrac a, Integral b) => a -> b
round (Dimension -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
shFloat -> Float -> Float
forall a. Num a => a -> a -> a
*Float
cy)
else
Dimension
sh
cbottom:: Float -> Rectangle -> Rectangle
cbottom :: Float -> Rectangle -> Rectangle
cbottom Float
cy (Rectangle Position
sx Position
sy Dimension
sw Dimension
sh) = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
sx Position
y Dimension
sw Dimension
h
where h :: Dimension
h = Float -> Dimension
forall a b. (RealFrac a, Integral b) => a -> b
round (Dimension -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
shFloat -> Float -> Float
forall a. Num a => a -> a -> a
*(Float
1Float -> Float -> Float
forall a. Num a => a -> a -> a
-Float
cy))
y :: Position
y = Float -> Position
forall a b. (RealFrac a, Integral b) => a -> b
round (Dimension -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
shFloat -> Float -> Float
forall a. Num a => a -> a -> a
*Float
cyFloat -> Float -> Float
forall a. Num a => a -> a -> a
+Position -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
sy)
cright:: Float -> Float -> Rectangle -> Rectangle
cright :: Float -> Float -> Rectangle -> Rectangle
cright Float
cx Float
cy (Rectangle Position
sx Position
sy Dimension
sw Dimension
sh) = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x Position
sy Dimension
w Dimension
h
where w :: Dimension
w = Float -> Dimension
forall a b. (RealFrac a, Integral b) => a -> b
round (Dimension -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
swFloat -> Float -> Float
forall a. Num a => a -> a -> a
*(Float
1Float -> Float -> Float
forall a. Num a => a -> a -> a
-Float
cx))
x :: Position
x = Float -> Position
forall a b. (RealFrac a, Integral b) => a -> b
round (Dimension -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
swFloat -> Float -> Float
forall a. Num a => a -> a -> a
*Float
cxFloat -> Float -> Float
forall a. Num a => a -> a -> a
+Position -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
sx)
h :: Dimension
h = Float -> Dimension
forall a b. (RealFrac a, Integral b) => a -> b
round (Dimension -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
shFloat -> Float -> Float
forall a. Num a => a -> a -> a
*Float
cy)
divideBottom :: Rectangle -> [a] -> [(a, Rectangle)]
divideBottom :: forall a. Rectangle -> [a] -> [(a, Rectangle)]
divideBottom (Rectangle Position
x Position
y Dimension
w Dimension
h) [a]
ws = [a] -> [Rectangle] -> [(a, Rectangle)]
forall a b. [a] -> [b] -> [(a, b)]
zip [a]
ws [Rectangle]
rects
where n :: Int
n = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
ws
oneW :: Int
oneW = Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
w Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
n
oneRect :: Rectangle
oneRect = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x Position
y (Int -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
oneW) Dimension
h
rects :: [Rectangle]
rects = Int -> [Rectangle] -> [Rectangle]
forall a. Int -> [a] -> [a]
take Int
n ([Rectangle] -> [Rectangle]) -> [Rectangle] -> [Rectangle]
forall a b. (a -> b) -> a -> b
$ (Rectangle -> Rectangle) -> Rectangle -> [Rectangle]
forall a. (a -> a) -> a -> [a]
iterate (Position -> Rectangle -> Rectangle
shiftR (Int -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
oneW)) Rectangle
oneRect
divideRight :: Rectangle -> [a] -> [(a, Rectangle)]
divideRight :: forall a. Rectangle -> [a] -> [(a, Rectangle)]
divideRight (Rectangle Position
x Position
y Dimension
w Dimension
h) [a]
ws = if Int
nInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0 then [] else [a] -> [Rectangle] -> [(a, Rectangle)]
forall a b. [a] -> [b] -> [(a, b)]
zip [a]
ws [Rectangle]
rects
where n :: Int
n = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
ws
oneH :: Int
oneH = Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
h Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
n
oneRect :: Rectangle
oneRect = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x Position
y Dimension
w (Int -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
oneH)
rects :: [Rectangle]
rects = Int -> [Rectangle] -> [Rectangle]
forall a. Int -> [a] -> [a]
take Int
n ([Rectangle] -> [Rectangle]) -> [Rectangle] -> [Rectangle]
forall a b. (a -> b) -> a -> b
$ (Rectangle -> Rectangle) -> Rectangle -> [Rectangle]
forall a. (a -> a) -> a -> [a]
iterate (Position -> Rectangle -> Rectangle
shiftB (Int -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
oneH)) Rectangle
oneRect
shiftR :: Position -> Rectangle -> Rectangle
shiftR :: Position -> Rectangle -> Rectangle
shiftR Position
s (Rectangle Position
x Position
y Dimension
w Dimension
h) = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Position
xPosition -> Position -> Position
forall a. Num a => a -> a -> a
+Position
s) Position
y Dimension
w Dimension
h
shiftB :: Position -> Rectangle -> Rectangle
shiftB :: Position -> Rectangle -> Rectangle
shiftB Position
s (Rectangle Position
x Position
y Dimension
w Dimension
h) = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x (Position
yPosition -> Position -> Position
forall a. Num a => a -> a -> a
+Position
s) Dimension
w Dimension
h