-- | Representation of an axis-aligned rectangle on a 2D plane, with one of its -- corners being a designated origin point. module Data.Text.ParagraphLayout.Internal.Rect ( Bias (LL, LH, HL, HH) , Rect (Rect, x_origin, y_origin, x_size, y_size) , height , union , unionMany , unionMany1 , width , x_max , x_min , x_terminus , y_max , y_min , y_terminus ) where import Data.List.NonEmpty (NonEmpty, nonEmpty) -- | An axis-aligned rectangle on a 2D plane. data Rect a = Rect { x_origin :: a -- ^ X coordinate of the corner designated as the rectangle's origin. , y_origin :: a -- ^ Y coordinate of the corner designated as the rectangle's origin. , x_size :: a -- ^ Signed difference between the X coordinates of the rectangle's sides. , y_size :: a -- ^ Signed difference between the Y coordinates of the rectangle's sides. } deriving (Eq, Read, Show) -- | Absolute difference between the X coordinates of the rectangle's sides. width :: Num a => Rect a -> a width r = abs $ x_size r -- | Absolute difference between the Y coordinates of the rectangle's sides. height :: Num a => Rect a -> a height r = abs $ y_size r -- | X coordinate of the corner opposite of the origin. x_terminus :: Num a => Rect a -> a x_terminus r = x_origin r + x_size r -- | Y coordinate of the corner opposite of the origin. y_terminus :: Num a => Rect a -> a y_terminus r = y_origin r + y_size r -- | The smaller of the two X coordinates of the rectangle's edges. x_min :: (Num a, Ord a) => Rect a -> a x_min r = x_origin r `min` x_terminus r -- | The smaller of the two Y coordinates of the rectangle's edges. y_min :: (Num a, Ord a) => Rect a -> a y_min r = y_origin r `min` y_terminus r -- | The larger of the two X coordinates of the rectangle's edges. x_max :: (Num a, Ord a) => Rect a -> a x_max r = x_origin r `max` x_terminus r -- | The larger of the two Y coordinates of the rectangle's edges. y_max :: (Num a, Ord a) => Rect a -> a y_max r = y_origin r `max` y_terminus r -- | Determines which corner of a calculated rectangle should be its origin. data Bias = LL -- ^ Set the origin as the corner with low X and low Y coordinates. | LH -- ^ Set the origin as the corner with low X and high Y coordinates. | HL -- ^ Set the origin as the corner with high X and low Y coordinates. | HH -- ^ Set the origin as the corner with high X and high Y coordinates. -- | The smallest rectangle completely containing the given two rectangles. -- -- The origin of the output rectangle will be set according to `Bias`, -- regardless of which corners of the input rectangles are designated -- as their origins. -- -- Note that this operation has no identity element. A rectangle whose -- `x_size` and/or `y_size` are zero is not considered null or neutral, -- but effectively acts as a point, which will be contained in the union. -- -- You can use `Nothing` as an identity element if you lift this operation -- over the `Maybe` applicative functor: -- -- @ -- `Control.Applicative.liftA2` (`union` bias) -- @ union :: (Num a, Ord a) => Bias -> Rect a -> Rect a -> Rect a union bias a b = case bias of LL -> Rect lx ly dx dy LH -> Rect lx hy dx (-dy) HL -> Rect hx ly (-dx) dy HH -> Rect hx hy (-dx) (-dy) where lx = x_min a `min` x_min b ly = y_min a `min` y_min b hx = x_max a `max` x_max b hy = y_max a `max` y_max b dx = hx - lx dy = hy - ly -- | `Just` the `union` of all given rectangles, or `Nothing` if none are given. unionMany :: (Num a, Ord a) => Bias -> [Rect a] -> Maybe (Rect a) unionMany bias rects = unionMany1 bias <$> nonEmpty rects -- | The `union` of all given rectangles, where at least one must be given. -- -- Note that adding a default value to the input list to make it non-empty -- will probably not do what you want, since the `union` operation has no -- identity element. -- -- If you need a default output value for empty inputs, consider using: -- -- @ -- `Data.Maybe.fromMaybe` yourDefaultValue $ `unionMany` bias rects -- @ unionMany1 :: (Num a, Ord a) => Bias -> NonEmpty (Rect a) -> Rect a unionMany1 bias rects = foldr1 (union bias) rects