Copyright | (c) 2018 Yclept Nemo |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
A module for handling pixel rectangles: Rectangle
.
Synopsis
- data PointRectangle a = PointRectangle {}
- pixelsToIndices :: Rectangle -> PointRectangle Integer
- pixelsToCoordinates :: Rectangle -> PointRectangle Integer
- indicesToRectangle :: PointRectangle Integer -> Rectangle
- coordinatesToRectangle :: PointRectangle Integer -> Rectangle
- empty :: Rectangle -> Bool
- intersects :: Rectangle -> Rectangle -> Bool
- supersetOf :: Rectangle -> Rectangle -> Bool
- difference :: Rectangle -> Rectangle -> [Rectangle]
- withBorder :: Integer -> Integer -> Integer -> Integer -> Integer -> Rectangle -> Rectangle
- center :: Rectangle -> (Ratio Integer, Ratio Integer)
- toRatio :: Rectangle -> Rectangle -> RationalRect
Usage
import XMonad.Util.Rectangle as R R.empty (Rectangle 0 0 1024 768)
data PointRectangle a Source #
Rectangle as two points. What those points mean depends on the conversion function.
Instances
Read a => Read (PointRectangle a) Source # | |
Defined in XMonad.Util.Rectangle readsPrec :: Int -> ReadS (PointRectangle a) # readList :: ReadS [PointRectangle a] # readPrec :: ReadPrec (PointRectangle a) # readListPrec :: ReadPrec [PointRectangle a] # | |
Show a => Show (PointRectangle a) Source # | |
Defined in XMonad.Util.Rectangle showsPrec :: Int -> PointRectangle a -> ShowS # show :: PointRectangle a -> String # showList :: [PointRectangle a] -> ShowS # | |
Eq a => Eq (PointRectangle a) Source # | |
Defined in XMonad.Util.Rectangle (==) :: PointRectangle a -> PointRectangle a -> Bool # (/=) :: PointRectangle a -> PointRectangle a -> Bool # |
pixelsToIndices :: Rectangle -> PointRectangle Integer Source #
There are three possible ways to convert rectangles to pixels:
- Consider integers as "gaps" between pixels; pixels range from
(N,N+1)
, exclusively:(0,1)
,(1,2)
, and so on. This leads to interval ambiguity: whether an integer endpoint contains a pixel depends on which direction the interval approaches the pixel. Consider the adjacent pixels(0,1)
and(1,2)
where1
can refer to either pixel(0,1)
or pixel(1,2)
. - Consider integers to demarcate the start of each pixel; pixels range from
[N,N+1)
:[0,1)
,[1,2)
, and so on - or equivalently:(N,N+1]
. This is the most flexible coordinate system, and the convention used by theRectangle
type. - Consider integers to demarcate the center of each pixel; pixels range from
[N,N+1]
, as though each real-valued coordinate had been rounded (either down or up) to the nearest integers. So each pixel, from zero, is listed as:[0,0]
,[1,1]
,[2,2]
, and so on. Rather than a coordinate system, this considers pixels as row/column indices. While easiest to reason with, indices are unable to represent zero-dimension rectangles.
Consider pixels as indices. Do not use this on empty rectangles.
pixelsToCoordinates :: Rectangle -> PointRectangle Integer Source #
Consider pixels as [N,N+1)
coordinates. Available for empty rectangles.
indicesToRectangle :: PointRectangle Integer -> Rectangle Source #
Invert pixelsToIndices
.
empty :: Rectangle -> Bool Source #
True if either the rect_width
or rect_height
fields are zero, i.e. the
rectangle has no area.
intersects :: Rectangle -> Rectangle -> Bool Source #
True if the intersection of the set of points comprising each rectangle is not the empty set. Therefore any rectangle containing the initial points of an empty rectangle will never intersect that rectangle - including the same empty rectangle.
supersetOf :: Rectangle -> Rectangle -> Bool Source #
True if the first rectangle contains at least all the points of the second rectangle. Any rectangle containing the initial points of an empty rectangle will be a superset of that rectangle - including the same empty rectangle.
difference :: Rectangle -> Rectangle -> [Rectangle] Source #
Return the smallest set of rectangles resulting from removing all the
points of the second rectangle from those of the first, i.e. r1 - r2
, such
that 0 <= l <= 4
where l
is the length of the resulting list.
:: Integer | Top border. |
-> Integer | Bottom border. |
-> Integer | Right border. |
-> Integer | Left border. |
-> Integer | Smallest allowable rectangle dimensions, i.e.
width/height, with values |
-> Rectangle | |
-> Rectangle |
Fit a Rectangle
within the given borders of itself. Given insufficient
space, borders are minimized while preserving the ratio of opposite borders.
Origin is top-left, and yes, negative borders are allowed.
center :: Rectangle -> (Ratio Integer, Ratio Integer) Source #
Calculate the center - (x,y)
- as if the Rectangle
were bounded.
toRatio :: Rectangle -> Rectangle -> RationalRect Source #
Invert scaleRationalRect
. Since that operation is lossy a roundtrip
conversion may not result in the original value. The first Rectangle
is
scaled to the second:
>>>
(Rectangle 2 2 6 6) `toRatio` (Rectangle 0 0 10 10)
RationalRect (1 % 5) (1 % 5) (3 % 5) (3 % 5)