module XMonad.Util.Rectangle
(
PointRectangle (..)
, pixelsToIndices, pixelsToCoordinates
, indicesToRectangle, coordinatesToRectangle
, empty
, intersects
, supersetOf
, difference
, withBorder
, center
, toRatio
) where
import XMonad
import XMonad.Prelude (fi)
import qualified XMonad.StackSet as W
import Data.Ratio
data PointRectangle a = PointRectangle
{ forall a. PointRectangle a -> a
point_x1::a
, forall a. PointRectangle a -> a
point_y1::a
, forall a. PointRectangle a -> a
point_x2::a
, forall a. PointRectangle a -> a
point_y2::a
} deriving (PointRectangle a -> PointRectangle a -> Bool
(PointRectangle a -> PointRectangle a -> Bool)
-> (PointRectangle a -> PointRectangle a -> Bool)
-> Eq (PointRectangle a)
forall a. Eq a => PointRectangle a -> PointRectangle a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => PointRectangle a -> PointRectangle a -> Bool
== :: PointRectangle a -> PointRectangle a -> Bool
$c/= :: forall a. Eq a => PointRectangle a -> PointRectangle a -> Bool
/= :: PointRectangle a -> PointRectangle a -> Bool
Eq,ReadPrec [PointRectangle a]
ReadPrec (PointRectangle a)
Int -> ReadS (PointRectangle a)
ReadS [PointRectangle a]
(Int -> ReadS (PointRectangle a))
-> ReadS [PointRectangle a]
-> ReadPrec (PointRectangle a)
-> ReadPrec [PointRectangle a]
-> Read (PointRectangle a)
forall a. Read a => ReadPrec [PointRectangle a]
forall a. Read a => ReadPrec (PointRectangle a)
forall a. Read a => Int -> ReadS (PointRectangle a)
forall a. Read a => ReadS [PointRectangle a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall a. Read a => Int -> ReadS (PointRectangle a)
readsPrec :: Int -> ReadS (PointRectangle a)
$creadList :: forall a. Read a => ReadS [PointRectangle a]
readList :: ReadS [PointRectangle a]
$creadPrec :: forall a. Read a => ReadPrec (PointRectangle a)
readPrec :: ReadPrec (PointRectangle a)
$creadListPrec :: forall a. Read a => ReadPrec [PointRectangle a]
readListPrec :: ReadPrec [PointRectangle a]
Read,Int -> PointRectangle a -> ShowS
[PointRectangle a] -> ShowS
PointRectangle a -> String
(Int -> PointRectangle a -> ShowS)
-> (PointRectangle a -> String)
-> ([PointRectangle a] -> ShowS)
-> Show (PointRectangle a)
forall a. Show a => Int -> PointRectangle a -> ShowS
forall a. Show a => [PointRectangle a] -> ShowS
forall a. Show a => PointRectangle a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> PointRectangle a -> ShowS
showsPrec :: Int -> PointRectangle a -> ShowS
$cshow :: forall a. Show a => PointRectangle a -> String
show :: PointRectangle a -> String
$cshowList :: forall a. Show a => [PointRectangle a] -> ShowS
showList :: [PointRectangle a] -> ShowS
Show)
pixelsToIndices :: Rectangle -> PointRectangle Integer
pixelsToIndices :: Rectangle -> PointRectangle Integer
pixelsToIndices (Rectangle Position
px Position
py Dimension
dx Dimension
dy) =
Integer -> Integer -> Integer -> Integer -> PointRectangle Integer
forall a. a -> a -> a -> a -> PointRectangle a
PointRectangle (Position -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
px)
(Position -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
py)
(Position -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
px Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Dimension -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
dx Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1)
(Position -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
py Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Dimension -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
dy Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1)
pixelsToCoordinates :: Rectangle -> PointRectangle Integer
pixelsToCoordinates :: Rectangle -> PointRectangle Integer
pixelsToCoordinates (Rectangle Position
px Position
py Dimension
dx Dimension
dy) =
Integer -> Integer -> Integer -> Integer -> PointRectangle Integer
forall a. a -> a -> a -> a -> PointRectangle a
PointRectangle (Position -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
px)
(Position -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
py)
(Position -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
px Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Dimension -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
dx)
(Position -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
py Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Dimension -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
dy)
indicesToRectangle :: PointRectangle Integer -> Rectangle
indicesToRectangle :: PointRectangle Integer -> Rectangle
indicesToRectangle (PointRectangle Integer
x1 Integer
y1 Integer
x2 Integer
y2) =
Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Integer -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x1)
(Integer -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
y1)
(Integer -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Dimension) -> Integer -> Dimension
forall a b. (a -> b) -> a -> b
$ Integer
x2 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
x1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1)
(Integer -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Dimension) -> Integer -> Dimension
forall a b. (a -> b) -> a -> b
$ Integer
y2 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
y1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1)
coordinatesToRectangle :: PointRectangle Integer -> Rectangle
coordinatesToRectangle :: PointRectangle Integer -> Rectangle
coordinatesToRectangle (PointRectangle Integer
x1 Integer
y1 Integer
x2 Integer
y2) =
Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Integer -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x1)
(Integer -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
y1)
(Integer -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Dimension) -> Integer -> Dimension
forall a b. (a -> b) -> a -> b
$ Integer
x2 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
x1)
(Integer -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Dimension) -> Integer -> Dimension
forall a b. (a -> b) -> a -> b
$ Integer
y2 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
y1)
empty :: Rectangle -> Bool
empty :: Rectangle -> Bool
empty (Rectangle Position
_ Position
_ Dimension
_ Dimension
0) = Bool
True
empty (Rectangle Position
_ Position
_ Dimension
0 Dimension
_) = Bool
True
empty Rectangle{} = Bool
False
intersects :: Rectangle -> Rectangle -> Bool
intersects :: Rectangle -> Rectangle -> Bool
intersects Rectangle
r1 Rectangle
r2 | Rectangle -> Bool
empty Rectangle
r1 Bool -> Bool -> Bool
|| Rectangle -> Bool
empty Rectangle
r2 = Bool
False
| Bool
otherwise = Integer
r1_x1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
r2_x2
Bool -> Bool -> Bool
&& Integer
r1_x2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
r2_x1
Bool -> Bool -> Bool
&& Integer
r1_y1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
r2_y2
Bool -> Bool -> Bool
&& Integer
r1_y2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
r2_y1
where PointRectangle Integer
r1_x1 Integer
r1_y1 Integer
r1_x2 Integer
r1_y2 = Rectangle -> PointRectangle Integer
pixelsToCoordinates Rectangle
r1
PointRectangle Integer
r2_x1 Integer
r2_y1 Integer
r2_x2 Integer
r2_y2 = Rectangle -> PointRectangle Integer
pixelsToCoordinates Rectangle
r2
supersetOf :: Rectangle -> Rectangle -> Bool
supersetOf :: Rectangle -> Rectangle -> Bool
supersetOf Rectangle
r1 Rectangle
r2 = Integer
r1_x1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
r2_x1
Bool -> Bool -> Bool
&& Integer
r1_y1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
r2_y1
Bool -> Bool -> Bool
&& Integer
r1_x2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
r2_x2
Bool -> Bool -> Bool
&& Integer
r1_y2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
r2_y2
where PointRectangle Integer
r1_x1 Integer
r1_y1 Integer
r1_x2 Integer
r1_y2 = Rectangle -> PointRectangle Integer
pixelsToCoordinates Rectangle
r1
PointRectangle Integer
r2_x1 Integer
r2_y1 Integer
r2_x2 Integer
r2_y2 = Rectangle -> PointRectangle Integer
pixelsToCoordinates Rectangle
r2
difference :: Rectangle -> Rectangle -> [Rectangle]
difference :: Rectangle -> Rectangle -> [Rectangle]
difference Rectangle
r1 Rectangle
r2 | Rectangle
r1 Rectangle -> Rectangle -> Bool
`intersects` Rectangle
r2 = (PointRectangle Integer -> Rectangle)
-> [PointRectangle Integer] -> [Rectangle]
forall a b. (a -> b) -> [a] -> [b]
map PointRectangle Integer -> Rectangle
coordinatesToRectangle ([PointRectangle Integer] -> [Rectangle])
-> [PointRectangle Integer] -> [Rectangle]
forall a b. (a -> b) -> a -> b
$
[[PointRectangle Integer]] -> [PointRectangle Integer]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[PointRectangle Integer]
rt,[PointRectangle Integer]
rr,[PointRectangle Integer]
rb,[PointRectangle Integer]
rl]
| Bool
otherwise = [Rectangle
r1]
where PointRectangle Integer
r1_x1 Integer
r1_y1 Integer
r1_x2 Integer
r1_y2 = Rectangle -> PointRectangle Integer
pixelsToCoordinates Rectangle
r1
PointRectangle Integer
r2_x1 Integer
r2_y1 Integer
r2_x2 Integer
r2_y2 = Rectangle -> PointRectangle Integer
pixelsToCoordinates Rectangle
r2
rt :: [PointRectangle Integer]
rt = [Integer -> Integer -> Integer -> Integer -> PointRectangle Integer
forall a. a -> a -> a -> a -> PointRectangle a
PointRectangle (Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
max Integer
r2_x1 Integer
r1_x1) Integer
r1_y1 Integer
r1_x2 Integer
r2_y1 | Integer
r2_y1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
r1_y1 Bool -> Bool -> Bool
&& Integer
r2_y1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
r1_y2]
rr :: [PointRectangle Integer]
rr = [Integer -> Integer -> Integer -> Integer -> PointRectangle Integer
forall a. a -> a -> a -> a -> PointRectangle a
PointRectangle Integer
r2_x2 (Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
max Integer
r2_y1 Integer
r1_y1) Integer
r1_x2 Integer
r1_y2 | Integer
r2_x2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
r1_x1 Bool -> Bool -> Bool
&& Integer
r2_x2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
r1_x2]
rb :: [PointRectangle Integer]
rb = [Integer -> Integer -> Integer -> Integer -> PointRectangle Integer
forall a. a -> a -> a -> a -> PointRectangle a
PointRectangle Integer
r1_x1 Integer
r2_y2 (Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
min Integer
r2_x2 Integer
r1_x2) Integer
r1_y2 | Integer
r2_y2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
r1_y1 Bool -> Bool -> Bool
&& Integer
r2_y2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
r1_y2]
rl :: [PointRectangle Integer]
rl = [Integer -> Integer -> Integer -> Integer -> PointRectangle Integer
forall a. a -> a -> a -> a -> PointRectangle a
PointRectangle Integer
r1_x1 Integer
r1_y1 Integer
r2_x1 (Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
min Integer
r2_y2 Integer
r1_y2) | Integer
r2_x1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
r1_x1 Bool -> Bool -> Bool
&& Integer
r2_x1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
r1_x2]
withBorder :: Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Rectangle -> Rectangle
withBorder :: Integer
-> Integer
-> Integer
-> Integer
-> Integer
-> Rectangle
-> Rectangle
withBorder Integer
t Integer
b Integer
r Integer
l Integer
i (Rectangle Position
x Position
y Dimension
w Dimension
h) =
let
w' :: Integer
w' = Dimension -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
w
h' :: Integer
h' = Dimension -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
h
i' :: Integer
i' = Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
max Integer
i Integer
0
iw :: Integer
iw = Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
min Integer
i' Integer
w'
ih :: Integer
ih = Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
min Integer
i' Integer
h'
bh :: Integer
bh = Integer
w' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
iw
bv :: Integer
bv = Integer
h' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
ih
rh :: Rational
rh = if Integer
l Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
r Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0
then Rational
1
else Rational -> Rational -> Rational
forall a. Ord a => a -> a -> a
min Rational
1 (Rational -> Rational) -> Rational -> Rational
forall a b. (a -> b) -> a -> b
$ Integer
bh Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% (Integer
l Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
r)
rv :: Rational
rv = if Integer
t Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
b Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0
then Rational
1
else Rational -> Rational -> Rational
forall a. Ord a => a -> a -> a
min Rational
1 (Rational -> Rational) -> Rational -> Rational
forall a b. (a -> b) -> a -> b
$ Integer
bv Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% (Integer
t Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
b)
t' :: Position
t' = Rational -> Position
forall b. Integral b => Rational -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Rational -> Position) -> Rational -> Position
forall a b. (a -> b) -> a -> b
$ Rational
rv Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Integer -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
t
b' :: Dimension
b' = Rational -> Dimension
forall b. Integral b => Rational -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Rational -> Dimension) -> Rational -> Dimension
forall a b. (a -> b) -> a -> b
$ Rational
rv Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Integer -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
b
r' :: Dimension
r' = Rational -> Dimension
forall b. Integral b => Rational -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Rational -> Dimension) -> Rational -> Dimension
forall a b. (a -> b) -> a -> b
$ Rational
rh Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Integer -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
r
l' :: Position
l' = Rational -> Position
forall b. Integral b => Rational -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Rational -> Position) -> Rational -> Position
forall a b. (a -> b) -> a -> b
$ Rational
rh Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Integer -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
l
in Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Position
x Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Position
l')
(Position
y Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Position
t')
(Dimension
w Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
r' Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Position -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
l')
(Dimension
h Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
b' Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Position -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
t')
center :: Rectangle -> (Ratio Integer,Ratio Integer)
center :: Rectangle -> (Rational, Rational)
center (Rectangle Position
x Position
y Dimension
w Dimension
h) = (Rational
cx,Rational
cy)
where cx :: Rational
cx = Position -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
x Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Dimension -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
w Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
2
cy :: Rational
cy = Position -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
y Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Dimension -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Dimension
h Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
2
toRatio :: Rectangle -> Rectangle -> W.RationalRect
toRatio :: Rectangle -> Rectangle -> RationalRect
toRatio (Rectangle Position
x1 Position
y1 Dimension
w1 Dimension
h1) (Rectangle Position
x2 Position
y2 Dimension
w2 Dimension
h2) =
Rational -> Rational -> Rational -> Rational -> RationalRect
W.RationalRect ((Position -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Position
x1 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
- Position -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Position
x2) Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
w2)
((Position -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Position
y1 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
- Position -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Position
y2) Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
h2)
(Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
w1 Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
w2) (Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
h1 Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
h2)