{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TupleSections #-}
module XMonad.Layout.ResizableThreeColumns (
ResizableThreeCol(..), MirrorResize(..)
) where
import XMonad hiding (splitVertically)
import XMonad.Prelude
import XMonad.Layout.ResizableTile(MirrorResize(..))
import qualified XMonad.StackSet as W
import qualified Data.Map as M
import Data.Ratio
data ResizableThreeCol a
= ResizableThreeColMid
{ forall a. ResizableThreeCol a -> Int
threeColNMaster :: !Int
, forall a. ResizableThreeCol a -> Rational
threeColDelta :: !Rational
, forall a. ResizableThreeCol a -> Rational
threeColFrac :: !Rational
, forall a. ResizableThreeCol a -> [Rational]
threeColSlaves :: [Rational]
}
| ResizableThreeCol
{ threeColNMaster :: !Int
, threeColDelta :: !Rational
, threeColFrac :: !Rational
, threeColSlaves :: [Rational]
} deriving (Int -> ResizableThreeCol a -> ShowS
[ResizableThreeCol a] -> ShowS
ResizableThreeCol a -> String
(Int -> ResizableThreeCol a -> ShowS)
-> (ResizableThreeCol a -> String)
-> ([ResizableThreeCol a] -> ShowS)
-> Show (ResizableThreeCol a)
forall a. Int -> ResizableThreeCol a -> ShowS
forall a. [ResizableThreeCol a] -> ShowS
forall a. ResizableThreeCol a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResizableThreeCol a] -> ShowS
$cshowList :: forall a. [ResizableThreeCol a] -> ShowS
show :: ResizableThreeCol a -> String
$cshow :: forall a. ResizableThreeCol a -> String
showsPrec :: Int -> ResizableThreeCol a -> ShowS
$cshowsPrec :: forall a. Int -> ResizableThreeCol a -> ShowS
Show,ReadPrec [ResizableThreeCol a]
ReadPrec (ResizableThreeCol a)
Int -> ReadS (ResizableThreeCol a)
ReadS [ResizableThreeCol a]
(Int -> ReadS (ResizableThreeCol a))
-> ReadS [ResizableThreeCol a]
-> ReadPrec (ResizableThreeCol a)
-> ReadPrec [ResizableThreeCol a]
-> Read (ResizableThreeCol a)
forall a. ReadPrec [ResizableThreeCol a]
forall a. ReadPrec (ResizableThreeCol a)
forall a. Int -> ReadS (ResizableThreeCol a)
forall a. ReadS [ResizableThreeCol a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResizableThreeCol a]
$creadListPrec :: forall a. ReadPrec [ResizableThreeCol a]
readPrec :: ReadPrec (ResizableThreeCol a)
$creadPrec :: forall a. ReadPrec (ResizableThreeCol a)
readList :: ReadS [ResizableThreeCol a]
$creadList :: forall a. ReadS [ResizableThreeCol a]
readsPrec :: Int -> ReadS (ResizableThreeCol a)
$creadsPrec :: forall a. Int -> ReadS (ResizableThreeCol a)
Read)
instance LayoutClass ResizableThreeCol a where
doLayout :: ResizableThreeCol a
-> Rectangle
-> Stack a
-> X ([(a, Rectangle)], Maybe (ResizableThreeCol a))
doLayout (ResizableThreeCol Int
n Rational
_ Rational
f [Rational]
mf) Rectangle
r = Bool
-> Int
-> Rational
-> [Rational]
-> Rectangle
-> Stack a
-> X ([(a, Rectangle)], Maybe (ResizableThreeCol a))
forall a (layout :: * -> *).
Bool
-> Int
-> Rational
-> [Rational]
-> Rectangle
-> Stack a
-> X ([(a, Rectangle)], Maybe (layout a))
doL Bool
False Int
n Rational
f [Rational]
mf Rectangle
r
doLayout (ResizableThreeColMid Int
n Rational
_ Rational
f [Rational]
mf) Rectangle
r = Bool
-> Int
-> Rational
-> [Rational]
-> Rectangle
-> Stack a
-> X ([(a, Rectangle)], Maybe (ResizableThreeCol a))
forall a (layout :: * -> *).
Bool
-> Int
-> Rational
-> [Rational]
-> Rectangle
-> Stack a
-> X ([(a, Rectangle)], Maybe (layout a))
doL Bool
True Int
n Rational
f [Rational]
mf Rectangle
r
handleMessage :: ResizableThreeCol a
-> SomeMessage -> X (Maybe (ResizableThreeCol a))
handleMessage ResizableThreeCol a
l SomeMessage
m = do
Maybe (Stack Window)
ms <- Workspace String (Layout Window) Window -> Maybe (Stack Window)
forall i l a. Workspace i l a -> Maybe (Stack a)
W.stack (Workspace String (Layout Window) Window -> Maybe (Stack Window))
-> (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window)
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Maybe (Stack Window)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
W.workspace (Screen String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window)
-> (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
W.current (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Maybe (Stack Window))
-> X (StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> X (Maybe (Stack Window))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (XState
-> StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> X (StackSet String (Layout Window) Window ScreenId ScreenDetail)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
windowset
[Window]
fs <- Map Window RationalRect -> [Window]
forall k a. Map k a -> [k]
M.keys (Map Window RationalRect -> [Window])
-> (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Map Window RationalRect)
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
-> [Window]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackSet String (Layout Window) Window ScreenId ScreenDetail
-> Map Window RationalRect
forall i l a sid sd. StackSet i l a sid sd -> Map a RationalRect
W.floating (StackSet String (Layout Window) Window ScreenId ScreenDetail
-> [Window])
-> X (StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> X [Window]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (XState
-> StackSet String (Layout Window) Window ScreenId ScreenDetail)
-> X (StackSet String (Layout Window) Window ScreenId ScreenDetail)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState
-> StackSet String (Layout Window) Window ScreenId ScreenDetail
windowset
Maybe (ResizableThreeCol a) -> X (Maybe (ResizableThreeCol a))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (ResizableThreeCol a) -> X (Maybe (ResizableThreeCol a)))
-> Maybe (ResizableThreeCol a) -> X (Maybe (ResizableThreeCol a))
forall a b. (a -> b) -> a -> b
$ do
Stack Window
s <- Maybe (Stack Window)
ms
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Stack Window -> Window
forall a. Stack a -> a
W.focus Stack Window
s Window -> [Window] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Window]
fs)
let s' :: Stack Window
s' = Stack Window
s { up :: [Window]
W.up = Stack Window -> [Window]
forall a. Stack a -> [a]
W.up Stack Window
s [Window] -> [Window] -> [Window]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Window]
fs, down :: [Window]
W.down = Stack Window -> [Window]
forall a. Stack a -> [a]
W.down Stack Window
s [Window] -> [Window] -> [Window]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Window]
fs }
[Maybe (ResizableThreeCol a)] -> Maybe (ResizableThreeCol a)
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [ (Resize -> ResizableThreeCol a)
-> Maybe Resize -> Maybe (ResizableThreeCol a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Resize -> ResizableThreeCol a
forall {a}. Resize -> ResizableThreeCol a
resize (SomeMessage -> Maybe Resize
forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
m)
, (MirrorResize -> ResizableThreeCol a)
-> Maybe MirrorResize -> Maybe (ResizableThreeCol a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Stack Window -> MirrorResize -> ResizableThreeCol a
forall {a} {a}. Stack a -> MirrorResize -> ResizableThreeCol a
mresize Stack Window
s') (SomeMessage -> Maybe MirrorResize
forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
m)
, (IncMasterN -> ResizableThreeCol a)
-> Maybe IncMasterN -> Maybe (ResizableThreeCol a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IncMasterN -> ResizableThreeCol a
forall {a}. IncMasterN -> ResizableThreeCol a
incmastern (SomeMessage -> Maybe IncMasterN
forall m. Message m => SomeMessage -> Maybe m
fromMessage SomeMessage
m)
]
where
resize :: Resize -> ResizableThreeCol a
resize Resize
Shrink = ResizableThreeCol a
l { threeColFrac :: Rational
threeColFrac = Rational -> Rational -> Rational
forall a. Ord a => a -> a -> a
max (-Rational
0.5) (Rational -> Rational) -> Rational -> Rational
forall a b. (a -> b) -> a -> b
$ Rational
fracRational -> Rational -> Rational
forall a. Num a => a -> a -> a
-Rational
delta }
resize Resize
Expand = ResizableThreeCol a
l { threeColFrac :: Rational
threeColFrac = Rational -> Rational -> Rational
forall a. Ord a => a -> a -> a
min Rational
1 (Rational -> Rational) -> Rational -> Rational
forall a b. (a -> b) -> a -> b
$ Rational
fracRational -> Rational -> Rational
forall a. Num a => a -> a -> a
+Rational
delta }
mresize :: Stack a -> MirrorResize -> ResizableThreeCol a
mresize Stack a
s MirrorResize
MirrorShrink = Stack a -> Rational -> ResizableThreeCol a
forall {a} {a}. Stack a -> Rational -> ResizableThreeCol a
mresize' Stack a
s Rational
delta
mresize Stack a
s MirrorResize
MirrorExpand = Stack a -> Rational -> ResizableThreeCol a
forall {a} {a}. Stack a -> Rational -> ResizableThreeCol a
mresize' Stack a
s (Rational -> Rational
forall a. Num a => a -> a
negate Rational
delta)
mresize' :: Stack a -> Rational -> ResizableThreeCol a
mresize' Stack a
s Rational
delt =
let up :: Int
up = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([a] -> Int) -> [a] -> Int
forall a b. (a -> b) -> a -> b
$ Stack a -> [a]
forall a. Stack a -> [a]
W.up Stack a
s
total :: Int
total = Int
up Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Stack a -> [a]
forall a. Stack a -> [a]
W.down Stack a
s) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
pos :: Int
pos = if Int
up Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (Int
nmasterInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Bool -> Bool -> Bool
|| Int
up Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (Int
totalInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) then Int
upInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1 else Int
up
mfrac' :: [Rational]
mfrac' = [Rational] -> Rational -> Int -> [Rational]
forall {t} {t}. (Eq t, Num t, Num t) => [t] -> t -> t -> [t]
modifymfrac ([Rational]
mfrac [Rational] -> [Rational] -> [Rational]
forall a. [a] -> [a] -> [a]
++ Rational -> [Rational]
forall a. a -> [a]
repeat Rational
1) Rational
delt Int
pos
in ResizableThreeCol a
l { threeColSlaves :: [Rational]
threeColSlaves = Int -> [Rational] -> [Rational]
forall a. Int -> [a] -> [a]
take Int
total [Rational]
mfrac'}
modifymfrac :: [t] -> t -> t -> [t]
modifymfrac [] t
_ t
_ = []
modifymfrac (t
f:[t]
fx) t
d t
n
| t
n t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== t
0 = t
ft -> t -> t
forall a. Num a => a -> a -> a
+t
d t -> [t] -> [t]
forall a. a -> [a] -> [a]
: [t]
fx
| Bool
otherwise = t
f t -> [t] -> [t]
forall a. a -> [a] -> [a]
: [t] -> t -> t -> [t]
modifymfrac [t]
fx t
d (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1)
incmastern :: IncMasterN -> ResizableThreeCol a
incmastern (IncMasterN Int
x) = ResizableThreeCol a
l { threeColNMaster :: Int
threeColNMaster = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
nmasterInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
x) }
nmaster :: Int
nmaster = ResizableThreeCol a -> Int
forall a. ResizableThreeCol a -> Int
threeColNMaster ResizableThreeCol a
l
delta :: Rational
delta = ResizableThreeCol a -> Rational
forall a. ResizableThreeCol a -> Rational
threeColDelta ResizableThreeCol a
l
frac :: Rational
frac = ResizableThreeCol a -> Rational
forall a. ResizableThreeCol a -> Rational
threeColFrac ResizableThreeCol a
l
mfrac :: [Rational]
mfrac = ResizableThreeCol a -> [Rational]
forall a. ResizableThreeCol a -> [Rational]
threeColSlaves ResizableThreeCol a
l
description :: ResizableThreeCol a -> String
description ResizableThreeCol a
_ = String
"ResizableThreeCol"
doL :: Bool -> Int -> Rational -> [Rational] -> Rectangle
-> W.Stack a -> X ([(a, Rectangle)], Maybe (layout a))
doL :: forall a (layout :: * -> *).
Bool
-> Int
-> Rational
-> [Rational]
-> Rectangle
-> Stack a
-> X ([(a, Rectangle)], Maybe (layout a))
doL Bool
middle Int
nmaster Rational
f [Rational]
mf Rectangle
r =
([(a, Rectangle)], Maybe (layout a))
-> X ([(a, Rectangle)], Maybe (layout a))
forall (m :: * -> *) a. Monad m => a -> m a
return
(([(a, Rectangle)], Maybe (layout a))
-> X ([(a, Rectangle)], Maybe (layout a)))
-> (Stack a -> ([(a, Rectangle)], Maybe (layout a)))
-> Stack a
-> X ([(a, Rectangle)], Maybe (layout a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (, Maybe (layout a)
forall a. Maybe a
Nothing)
([(a, Rectangle)] -> ([(a, Rectangle)], Maybe (layout a)))
-> (Stack a -> [(a, Rectangle)])
-> Stack a
-> ([(a, Rectangle)], Maybe (layout a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([a] -> [Rectangle] -> [(a, Rectangle)])
-> ([a] -> [Rectangle]) -> [a] -> [(a, Rectangle)]
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap [a] -> [Rectangle] -> [(a, Rectangle)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Bool
-> Rational -> [Rational] -> Rectangle -> Int -> Int -> [Rectangle]
tile3 Bool
middle Rational
f ([Rational]
mf [Rational] -> [Rational] -> [Rational]
forall a. [a] -> [a] -> [a]
++ Rational -> [Rational]
forall a. a -> [a]
repeat Rational
1) Rectangle
r Int
nmaster (Int -> [Rectangle]) -> ([a] -> Int) -> [a] -> [Rectangle]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length) ([a] -> [(a, Rectangle)])
-> (Stack a -> [a]) -> Stack a -> [(a, Rectangle)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stack a -> [a]
forall a. Stack a -> [a]
W.integrate
tile3 :: Bool -> Rational -> [Rational] -> Rectangle -> Int -> Int -> [Rectangle]
tile3 :: Bool
-> Rational -> [Rational] -> Rectangle -> Int -> Int -> [Rectangle]
tile3 Bool
middle Rational
f [Rational]
mf Rectangle
r Int
nmaster Int
n
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
nmaster Bool -> Bool -> Bool
|| Int
nmaster Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = [Rational] -> Int -> Rectangle -> [Rectangle]
forall r. RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
splitVertically [Rational]
mf Int
n Rectangle
r
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
nmasterInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1 = [Rational] -> Int -> Rectangle -> [Rectangle]
forall r. RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
splitVertically [Rational]
mf Int
nmaster Rectangle
s1
[Rectangle] -> [Rectangle] -> [Rectangle]
forall a. [a] -> [a] -> [a]
++ [Rational] -> Int -> Rectangle -> [Rectangle]
forall r. RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
splitVertically (Int -> [Rational] -> [Rational]
forall a. Int -> [a] -> [a]
drop Int
nmaster [Rational]
mf) (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
nmaster) Rectangle
s2
| Bool
otherwise = [[Rectangle]] -> [Rectangle]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [Rational] -> Int -> Rectangle -> [Rectangle]
forall r. RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
splitVertically [Rational]
mf Int
nmaster Rectangle
r1
, [Rational] -> Int -> Rectangle -> [Rectangle]
forall r. RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
splitVertically (Int -> [Rational] -> [Rational]
forall a. Int -> [a] -> [a]
drop Int
nmaster [Rational]
mf) Int
nslave1 Rectangle
r2
, [Rational] -> Int -> Rectangle -> [Rectangle]
forall r. RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
splitVertically (Int -> [Rational] -> [Rational]
forall a. Int -> [a] -> [a]
drop (Int
nmaster Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
nslave1) [Rational]
mf) Int
nslave2 Rectangle
r3
]
where
(Rectangle
r1, Rectangle
r2, Rectangle
r3) = Bool -> Rational -> Rectangle -> (Rectangle, Rectangle, Rectangle)
split3HorizontallyBy Bool
middle (if Rational
fRational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
<Rational
0 then Rational
1Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+Rational
2Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
*Rational
f else Rational
f) Rectangle
r
(Rectangle
s1, Rectangle
s2) = Rational -> Rectangle -> (Rectangle, Rectangle)
forall r. RealFrac r => r -> Rectangle -> (Rectangle, Rectangle)
splitHorizontallyBy (if Rational
fRational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
<Rational
0 then Rational
1Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+Rational
f else Rational
f) Rectangle
r
nslave :: Int
nslave = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
nmaster
nslave1 :: Int
nslave1 = Ratio Int -> Int
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Int
nslave Int -> Int -> Ratio Int
forall a. Integral a => a -> a -> Ratio a
% Int
2)
nslave2 :: Int
nslave2 = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
nmaster Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
nslave1
splitVertically :: RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
splitVertically :: forall r. RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
splitVertically [] Int
_ Rectangle
r = [Rectangle
r]
splitVertically [r]
_ Int
n Rectangle
r | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
2 = [Rectangle
r]
splitVertically (r
f:[r]
fx) Int
n (Rectangle Position
sx Position
sy Dimension
sw Dimension
sh) =
let smallh :: Dimension
smallh = Dimension -> Dimension -> Dimension
forall a. Ord a => a -> a -> a
min Dimension
sh (r -> Dimension
forall a b. (RealFrac a, Integral b) => a -> b
floor (r -> Dimension) -> r -> Dimension
forall a b. (a -> b) -> a -> b
$ Dimension -> r
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Dimension
sh Dimension -> Dimension -> Dimension
forall a. Integral a => a -> a -> a
`div` Int -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) r -> r -> r
forall a. Num a => a -> a -> a
* r
f)
in Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
sx Position
sy Dimension
sw Dimension
smallh Rectangle -> [Rectangle] -> [Rectangle]
forall a. a -> [a] -> [a]
:
[r] -> Int -> Rectangle -> [Rectangle]
forall r. RealFrac r => [r] -> Int -> Rectangle -> [Rectangle]
splitVertically [r]
fx (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
sx (Position
syPosition -> Position -> Position
forall a. Num a => a -> a -> a
+Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
smallh) Dimension
sw (Dimension
shDimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
-Dimension
smallh))
split3HorizontallyBy :: Bool -> Rational -> Rectangle -> (Rectangle, Rectangle, Rectangle)
split3HorizontallyBy :: Bool -> Rational -> Rectangle -> (Rectangle, Rectangle, Rectangle)
split3HorizontallyBy Bool
middle Rational
f (Rectangle Position
sx Position
sy Dimension
sw Dimension
sh) =
if Bool
middle
then ( Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Position
sx Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
r3w) Position
sy Dimension
r1w Dimension
sh
, Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Position
sx Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
r3w Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
r1w) Position
sy Dimension
r2w Dimension
sh
, Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
sx Position
sy Dimension
r3w Dimension
sh )
else ( Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
sx Position
sy Dimension
r1w Dimension
sh
, Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Position
sx Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
r1w) Position
sy Dimension
r2w Dimension
sh
, Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Position
sx Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
r1w Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
r2w) Position
sy Dimension
r3w Dimension
sh )
where
r1w :: Dimension
r1w = Rational -> Dimension
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Rational -> Dimension) -> Rational -> Dimension
forall a b. (a -> b) -> a -> b
$ Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
sw Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
f
r2w :: Dimension
r2w = Ratio Dimension -> Dimension
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Ratio Dimension -> Dimension) -> Ratio Dimension -> Dimension
forall a b. (a -> b) -> a -> b
$ (Dimension
sw Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
r1w) Dimension -> Dimension -> Ratio Dimension
forall a. Integral a => a -> a -> Ratio a
% Dimension
2
r3w :: Dimension
r3w = Dimension
sw Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
r1w Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
r2w