M lib/Data/Text/ParagraphLayout.hs => lib/Data/Text/ParagraphLayout.hs +14 -0
@@ 1,3 1,17 @@
+-- |
+--
+-- Positions and distances are represented as 32-bit integers. Their unit must
+-- be defined by the caller, who must calculate the desired dimensions of the
+-- EM square of the input font and set them using
+-- `Data.Text.Glyphize.optionScale`.
+--
+-- For example, if @1em = 20px@, if the output pixels are square, and if the
+-- output coordinates are in 1/64ths of a pixel, you should set the scale to
+-- @`Just` (1280, 1280)@.
+--
+-- X coordinates increase from left to right.
+--
+-- Y coordinates increase from bottom to top.
module Data.Text.ParagraphLayout
(Fragment(Fragment, fragmentPen, fragmentRect, fragmentGlyphs)
,LineHeight(Absolute, Normal)
M src/Data/Text/ParagraphLayout/Internal/Break.hs => src/Data/Text/ParagraphLayout/Internal/Break.hs +4 -4
@@ 1,10 1,10 @@
-- | Boundary analysis using `Data.Text.ICU`, but returning numeric offsets
-- instead of text slices.
--
--- Within this module, each /offset/ refers to the number of `Word8` items
--- (also called UTF-8 code units or bytes) between the start of the input `Text`
--- and the position of the break. The internal offset of the `Text` from the
--- start of its underlying byte array is excluded.
+-- Within this module, each /offset/ refers to the number of `Data.Word.Word8`
+-- items (also called UTF-8 code units or bytes) between the start of the input
+-- `Text` and the position of the break. The internal offset of the `Text` from
+-- the start of its underlying byte array is excluded.
module Data.Text.ParagraphLayout.Internal.Break (breaksDesc, subOffsetsDesc)
where
M src/Data/Text/ParagraphLayout/Internal/Fragment.hs => src/Data/Text/ParagraphLayout/Internal/Fragment.hs +16 -12
@@ 6,10 6,14 @@ import Data.Text.Glyphize (GlyphInfo, GlyphPos)
import Data.Text.ParagraphLayout.Internal.Rect
--- | Box fragment or fragment (CSS3), except that continuous text even within
--- one line can be split into multiple fragments because of spans or changes in
--- script.
+-- | A unit of text laid out in a rectangular area.
+--
+-- Equivalent to the CSS3 terms /box fragment/ or /fragment/, except that
+-- continuous text even within one line can be split into multiple fragments,
+-- either because it comes from multiple input spans, or because it contains
+-- glyphs from multiple scripts.
data Fragment = Fragment
+
{ fragmentRect :: Rect Int32
-- ^ Physical position of the fragment within the paragraph, calculated
-- using all glyph advances in this fragment and the calculated line height.
@@ 18,22 22,22 @@ data Fragment = Fragment
-- 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
+ -- 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 area to draw on – you need FreeType or a similar library for that.
--
-- The origin coordinates are relative to the paragraph.
- --
- -- The sizes can be positive or negative, depending on the text direction.
- --
- -- X coordinates increase from left to right.
- -- Y coordinates increase from bottom to top.
+
, fragmentPen :: (Int32, Int32)
-- ^ Coordinates of the initial pen position, from which the first glyph
- -- should be drawn. That glyph's `x_advance` or `y_advance` are then used
- -- to move the pen position for the next glyph.
+ -- should be drawn, relative to the origin of the `fragmentRect`.
+ -- Each glyph's `x_advance` or `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)
M src/Data/Text/ParagraphLayout/Internal/LineHeight.hs => src/Data/Text/ParagraphLayout/Internal/LineHeight.hs +1 -1
@@ 12,4 12,4 @@ data LineHeight
| Absolute Int32
-- ^ Set the preferred line height independently of the font.
- deriving (Eq, Show)
+ deriving (Eq, Read, Show)
M src/Data/Text/ParagraphLayout/Internal/Plain.hs => src/Data/Text/ParagraphLayout/Internal/Plain.hs +31 -20
@@ 1,13 1,3 @@
--- | Shaping for a paragraph of plain, unidirectional text using a single font.
---
--- The input text must be encoded as UTF-8 in a contiguous byte array.
---
--- Positions and distances are represented as 32-bit integers. Their unit must
--- be defined by the caller, who must calculate the desired dimensions of the
--- EM square of the input font and set them using @hb_font_set_scale()@. For
--- example, if @1em = 20px@, if the output pixels are square, and if the output
--- coordinates are in 1/64ths of a pixel, you should set both the @x_scale@ and
--- the @y_scale@ to @1280@.
module Data.Text.ParagraphLayout.Internal.Plain
(Paragraph(..)
,ParagraphLayout(..)
@@ 50,34 40,58 @@ import Data.Text.ParagraphLayout.Internal.Run
import Data.Text.ParagraphLayout.Internal.Span
import Data.Text.ParagraphLayout.Internal.TextContainer
--- | Text to be laid out as a paragraph.
+-- | Text to be laid out as a single paragraph.
--
-- May be divided into any number of neighbouring spans, each of which will
--- have its own layout rectangle(s) calculated.
+-- be represented as a separate `SpanLayout` in the resulting layout.
+--
+-- The input text must be encoded as UTF-8 in a contiguous byte array.
+--
+-- You may need to use "Data.Text.Internal" in order to determine the byte
+-- array and the necessary offsets to construct the paragraph without copying
+-- data.
+--
+-- For simple use cases, it may be sufficient to construct paragraphs using
+-- [ParagraphConstruction]("Data.Text.ParagraphLayout.ParagraphConstruction").
data Paragraph = Paragraph
Array
-- ^ A byte array containing the whole text to be laid out, in UTF-8.
Int
- -- ^ Byte offset of the first span.
+ -- ^ Byte offset of the first span from the start of the byte array.
-- Any characters preceding this offset will not be shaped, but may still
-- be used to influence the shape of neighbouring characters.
[Span]
-- ^ Parts of the text to be laid out, in logical order.
- -- The offset plus total length of all spans must not exceed array bounds.
+ -- The initial offset plus total length of all spans must not exceed
+ -- the bounds of the byte array.
-- Any characters following the last span will not be shaped, but may still
-- be used to influence the shape of neighbouring characters.
ParagraphOptions
- -- ^ Properties applying to the paragraph as a whole.
+ -- ^ Options applying to the paragraph as a whole.
data ParagraphOptions = ParagraphOptions
+
{ paragraphFont :: Font
+ -- ^ Font to be used for shaping and measurement.
+ -- Make sure to set its scale (see `Data.Text.Glyphize.optionScale`) using
+ -- the same units that you want in the output.
+
, paragraphLineHeight :: LineHeight
+ -- ^ Preferred line height of the resulting box fragments.
+
, paragraphMaxWidth :: Int32
+ -- ^ Line width at which line breaking should occur.
+ -- Lines will be broken at language-appropriate boundaries.
+ -- If a line still exceeds this limit then, it will be broken at character
+ -- boundaries, and if it already consists of a single cluster that cannot
+ -- be further broken down, it will overflow.
+
}
+ deriving (Eq, Show)
-- | The resulting layout of the whole paragraph.
data ParagraphLayout = ParagraphLayout
@@ 90,6 104,7 @@ data ParagraphLayout = ParagraphLayout
-- | The resulting layout of each span, which may include multiple fragments if
-- broken over multiple lines.
data SpanLayout = SpanLayout [Fragment]
+ -- TODO: Consider merging. fragments created by script changes.
deriving (Eq, Read, Show)
-- | Wrapper for temporarily mapping the relationship to a `Span`.
@@ 123,11 138,7 @@ base = Rect 0 0 0 0
containRects :: (Ord a, Num a) => [Rect a] -> Rect a
containRects = foldr union base
--- | Interface for basic plain text layout.
---
--- The entire paragraph will be assumed to have the same text direction and
--- will be shaped using a single font, starting from the left for LTR text or
--- from the right for RTL text.
+-- | Lay out a paragraph of plain, unidirectional text using a single font.
layoutPlain :: Paragraph -> ParagraphLayout
layoutPlain p@(Paragraph _ _ _ opts) = ParagraphLayout pRect sls
where
M src/Data/Text/ParagraphLayout/Internal/Run.hs => src/Data/Text/ParagraphLayout/Internal/Run.hs +3 -4
@@ 16,10 16,9 @@ import Data.Text.ParagraphLayout.Internal.Zipper
type ScriptCode = String
--- Each span can be broken into one or more runs by Balkón.
+-- | Each span can be broken into one or more runs by Balkón.
--
-- Each run could have a different script, language, or direction.
---
data Run = Run
{ runOffsetInSpan :: Int
, runText :: Text
@@ 44,7 43,7 @@ instance SeparableTextContainer Run where
type ProtoRun = (Zipper, Maybe Direction, ScriptCode)
--- Represents a zipper that can advance by at least one character.
+-- | Represents a zipper that can advance by at least one character.
data ZipperChoice = ZipperChoice
{ nextChar :: Char
, continuingRun :: Zipper
@@ 106,7 105,7 @@ foldRun x (previousRun@(_, d1, s1) : tailRuns) =
d2 = charDirection (nextChar x)
s2 = charScript (nextChar x)
--- Simplified detection of text direction for unidirectional text.
+-- | Simplified detection of text direction for unidirectional text.
mergeDirections :: Maybe Direction -> Maybe Direction -> Merged (Maybe Direction)
mergeDirections Nothing Nothing = Merged Nothing
mergeDirections (Just d1) Nothing = Merged (Just d1)
M src/Data/Text/ParagraphLayout/Internal/Script.hs => src/Data/Text/ParagraphLayout/Internal/Script.hs +1 -0
@@ 6,6 6,7 @@ where
-- hardcoded ranges, which may get out of sync with ICU.
import Unicode.Char.General.Scripts
+-- | A short script code for the given character, as expected by HarfBuzz.
charScript :: Char -> String
charScript = code . script
M src/Data/Text/ParagraphLayout/Internal/Span.hs => src/Data/Text/ParagraphLayout/Internal/Span.hs +3 -5
@@ 1,14 1,12 @@
module Data.Text.ParagraphLayout.Internal.Span (Span(..))
where
--- Paragraph is broken into spans by the caller.
+-- | A paragraph is broken into spans by the caller.
--
-- Each span could have a different font family, size, style, text decoration,
-- colour, language, etc.
---
--- TODO: Add all relevant attributes.
---
data Span = Span
+-- TODO: Add all relevant attributes.
{ spanLength :: Int
-- ^ Byte offset to the next span or the end of the paragraph text.
@@ 17,4 15,4 @@ data Span = Span
-- ^ Used for selecting the appropriate glyphs and line breaking rules.
}
- deriving (Show)
+ deriving (Eq, Read, Show)
M src/Data/Text/ParagraphLayout/Internal/TextContainer.hs => src/Data/Text/ParagraphLayout/Internal/TextContainer.hs +6 -2
@@ 12,15 12,19 @@ import Data.Text.Foreign (lengthWord8)
-- | Class of data types containing `Text` that can be accessed.
class TextContainer a where
+ -- | Extract a `Text` from its container.
getText :: a -> Text
-- | Class of data types containing `Text` that can be split at a given number
--- of `Word8` units from the start of the text.
+-- of `Data.Word.Word8` units from the start of the text.
class TextContainer a => SeparableTextContainer a where
+ -- | Split the given `SeparableTextContainer` at the given number of
+ -- `Data.Word.Word8` units from the start of the text, preserving whatever
+ -- constraints the instance requires.
splitTextAt8 :: Int -> a -> (a, a)
-- | Treat a list of text containers as a contiguous sequence,
--- and make a split at the given number of `Word8` from the beginning
+-- and make a split at the given number of `Data.Word.Word8` from the beginning
-- of this sequence.
--
-- If @n@ falls on a container boundary, the total number of output containers
M src/Data/Text/ParagraphLayout/Internal/Zipper.hs => src/Data/Text/ParagraphLayout/Internal/Zipper.hs +5 -5
@@ 91,7 91,7 @@ next :: Zipper -> Maybe Char
next = fmap fst . uncons . following
-- | /O(n)/ If @t@ is long enough to contain @n@ characters, return their size
--- in `Word8`.
+-- in `Data.Word.Word8`.
measureI8 :: Int -> Text -> Maybe Int
measureI8 n t =
let m = measureOff n t in
@@ 108,7 108,7 @@ recombine' (Text _ _ 0) t = t
recombine' t (Text _ _ 0) = t
recombine' (Text arr off len1) (Text _ _ len2) = Text arr off (len1 + len2)
--- | /O(1)/ Unsafely move the zipper forward @m@ `Word8` units.
+-- | /O(1)/ Unsafely move the zipper forward @m@ `Data.Word.Word8` units.
advanceByWord8 :: Int -> Zipper -> Zipper
advanceByWord8 m z = Zipper (recombine' a b) c
where
@@ 118,7 118,7 @@ advanceByWord8 m z = Zipper (recombine' a b) c
-- | /O(1)/ Unsafe version of `Data.Text.Foreign.dropWord8`.
--
--- Return the prefix of the `Text` of @m@ `Word8` units in length.
+-- Return the prefix of the `Text` of @m@ `Data.Word.Word8` units in length.
--
-- Requires that @m@ be within the bounds of the `Text`, not at the beginning
-- or at the end, and not inside a code point.
@@ 127,8 127,8 @@ takeWord8 m (Text arr off _) = Text arr off m
-- | /O(1)/ Unsafe version of `Data.Text.Foreign.dropWord8`.
--
--- Return the suffix of the `Text`, with @m@ `Word8` units dropped from its
--- beginning.
+-- Return the suffix of the `Text`, with @m@ `Data.Word.Word8` units dropped
+-- from its beginning.
--
-- Requires that @m@ be within the bounds of the `Text`, not at the beginning
-- or at the end, and not inside a code point.