module Data.Text.ParagraphLayout.Internal.Fragment ( Fragment (..) , ShapedRun , fragmentSpacedRect , shapedRun , shiftFragment ) where import Data.Int (Int32) import Data.Text.Glyphize (GlyphInfo, GlyphPos) import Data.Text.ParagraphLayout.Internal.AncestorBox import Data.Text.ParagraphLayout.Internal.Rect -- | A unit of text laid out in a rectangular area. -- -- Roughly equivalent to the term /text fragment/ as used in -- [CSS Display Module Level 3](https://www.w3.org/TR/css-display-3/). -- -- An input span (or /text sequence/ in CSS terms) can be broken into multiple -- fragments because of line breaking, because of bidirectional ordering, -- or because it contains glyphs from multiple scripts. data Fragment d = Fragment { fragmentUserData :: d -- ^ User-defined data associated with the input text span that produced -- this fragment. , fragmentLine :: Int -- ^ Logical number of the line box holding the fragment, starting at 1. -- Fragments with the same line number are on the same line and will not be -- separated by page breaks. , fragmentAncestorBoxes :: [AncestorBox d] -- ^ Information about inline boxes which contain this fragment -- (starting from the nearest ancestor and continuing upwards through the -- tree, up to but excluding the root) and the spacing required by them. , fragmentContentRect :: Rect Int32 -- ^ Physical position of the fragment within the paragraph, calculated -- using all glyph advances in this fragment and the used font's ascent -- and descent metrics. -- -- This is commonly used as the /content area/ of inline elements in -- web browsers, although this behaviour is not specified in CSS 2 -- nor in CSS Inline Layout Module Level 3. , fragmentRect :: Rect Int32 -- ^ Physical position of the fragment within the paragraph, calculated -- using all glyph advances in this fragment and the calculated line height. -- -- This is the space that the glyphs "take up" and is probably what you -- want to use for detecting position-based events such as mouse clicks. -- -- Beware that actual glyphs will not be drawn exactly to the borders of -- this rectangle -- they may be offset inwards and they can also extend -- outwards! -- -- These are not the typographic bounding boxes that you use for determining -- the area to draw on -- you need FreeType or a similar library for that. -- -- The origin coordinates are relative to the paragraph. -- -- The vertical extent of this rectangle is the equivalent of -- /layout bounds/ defined by CSS. -- -- Box spacing is not included. , fragmentPen :: (Int32, Int32) -- ^ Coordinates of the initial pen position, from which the first glyph -- should be drawn, relative to the origin of the `fragmentRect`. Each -- glyph's `Data.Text.Glyphize.x_advance` or `Data.Text.Glyphize.y_advance` -- are then used to move the pen position for the next glyph. , fragmentGlyphs :: [(GlyphInfo, GlyphPos)] -- ^ Glyphs contained in the fragment, as returned from HarfBuzz. } deriving (Eq, Read, Show) -- | Physical position of the fragment within the paragraph, with spacing -- added to the glyph advances. This is the space that the fragment takes up -- in the paragraph. fragmentSpacedRect :: Fragment d -> Rect Int32 fragmentSpacedRect (Fragment { fragmentRect = r, fragmentAncestorBoxes = bs }) | x_size r >= 0 = r { x_origin = x_origin r - leftSpacing , x_size = x_size r + leftSpacing + rightSpacing } | otherwise = r { x_origin = x_origin r + rightSpacing , x_size = x_size r - leftSpacing - rightSpacing } where leftSpacing = totalLeftSpacing bs rightSpacing = totalRightSpacing bs -- | A simplified representation of a box fragment, suitable for passing to a -- text drawing library but lacking detailed size information. type ShapedRun = (Int32, Int32, [(GlyphInfo, GlyphPos)]) -- | Convert a `Fragment` to a `ShapedRun`. shapedRun :: Fragment d -> ShapedRun shapedRun f = (x, y, g) where x = x_origin r + px y = y_origin r + py g = fragmentGlyphs f (px, py) = fragmentPen f r = fragmentRect f -- | Add @dx@ and @dy@ to the fragment's `x_origin` and `y_origin`, -- respectively. shiftFragment :: Int32 -> Int32 -> Fragment d -> Fragment d shiftFragment dx dy f = f' where f' = f { fragmentContentRect = cr', fragmentRect = r' } cr' = cr { x_origin = x_origin r + dx, y_origin = y_origin r + dy } cr = fragmentContentRect f r' = r { x_origin = x_origin r + dx, y_origin = y_origin r + dy } r = fragmentRect f