~jaro/balkon

ref: 810e30b3c54804be1608cdc347f79da42211783e balkon/src/Data/Text/ParagraphLayout/Internal/Layout.hs -rw-r--r-- 22.3 KiB
810e30b3Jaro Add manual test for mixed vertical alignment. 10 months ago
                                                                                
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
-- | Implementation of paragraph layout, decoupled from external interfaces.
module Data.Text.ParagraphLayout.Internal.Layout
    ( FragmentWithSpan
    , layoutAndAlignLines
    )
where

import Data.Foldable (toList)
import Data.Int (Int32)
import Data.List (mapAccumL)
import Data.List.NonEmpty (NonEmpty ((:|)), nonEmpty, (<|))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Maybe (fromMaybe)
import Data.Semigroup (sconcat)
import Data.Text.Foreign (lengthWord8)
import Data.Text.Glyphize
    ( Buffer (..)
    , ContentType (ContentTypeUnicode)
    , Direction (DirLTR, DirRTL, DirTTB, DirBTT)
    , FontExtents (..)
    , GlyphInfo
    , GlyphPos
    , defaultBuffer
    , fontExtentsForDir
    , shape
    )
import qualified Data.Text.ICU as BreakStatus (Line (Hard))
import qualified Data.Text.Lazy as Lazy

import Data.Text.ParagraphLayout.Internal.AncestorBox
import Data.Text.ParagraphLayout.Internal.ApplyBoxes
import Data.Text.ParagraphLayout.Internal.BiDiReorder
import Data.Text.ParagraphLayout.Internal.BoxOptions
import Data.Text.ParagraphLayout.Internal.Break
import Data.Text.ParagraphLayout.Internal.Fragment
import Data.Text.ParagraphLayout.Internal.LineHeight
import Data.Text.ParagraphLayout.Internal.ParagraphAlignment
import Data.Text.ParagraphLayout.Internal.ParagraphExtents
import qualified Data.Text.ParagraphLayout.Internal.ProtoFragment as PF
import qualified Data.Text.ParagraphLayout.Internal.ProtoLine as PL
import Data.Text.ParagraphLayout.Internal.Rect
import qualified Data.Text.ParagraphLayout.Internal.ResolvedBox as RB
import qualified Data.Text.ParagraphLayout.Internal.ResolvedSpan as RS
import Data.Text.ParagraphLayout.Internal.Run
import Data.Text.ParagraphLayout.Internal.SplitList
import Data.Text.ParagraphLayout.Internal.TextContainer
import Data.Text.ParagraphLayout.Internal.TextOptions
import qualified Data.Text.ParagraphLayout.Internal.VerticalOffsets as VO
import Data.Text.ParagraphLayout.Internal.WithSpan

-- This is redundant.
-- TODO: Consider using `ResolvedSpan` as `fragmentUserData`, then swapping it
--       for the actual `spanUserData` before returning it to the user.
type ProtoFragmentWithSpan d = WithSpan d PF.ProtoFragment
type FragmentWithSpan d = WithSpan d (Fragment d)
type ProtoFragmentWithBoxes d = WithBoxes d (ProtoFragmentWithSpan d)

-- | Create a multi-line layout from the given runs, splitting them as
-- necessary to fit within the requested line width.
--
-- The output is a flat list of fragments positioned in both dimensions.
layoutAndAlignLines
    :: Direction
    -> ParagraphAlignment
    -> Int32
    -> NonEmpty (WithSpan d Run)
    -> [FragmentWithSpan d]
layoutAndAlignLines dir align maxWidth runs = frags
    where
        frags = concatMap toList fragsInLines
        (_, fragsInLines) = mapAccumL positionLine originY numberedLines
        positionLine = positionLineH dir align maxWidth
        numberedLines = zip [1 ..] canonicalLines
        canonicalLines = fmap reorderProtoFragments visibleLines
        visibleLines = filter PL.visible logicalLines
        logicalLines = toList $ layoutLines maxWidth [] runs
        originY = paragraphOriginY

reorderProtoFragments :: PL.ProtoLine NonEmpty d -> PL.ProtoLine NonEmpty d
reorderProtoFragments pl@(PL.ProtoLine { PL.protoFragments = pfs }) =
    pl { PL.protoFragments = reorder pfs }

-- | Create a multi-line layout from the given runs, splitting them as
-- necessary to fit within the requested line width.
--
-- The output is a two-dimensional list of fragments positioned along the
-- horizontal axis.
layoutLines :: Int32 -> [RB.ResolvedBox d] -> NonEmpty (WithSpan d Run) ->
    NonEmpty (PL.ProtoLine NonEmpty d)
layoutLines maxWidth openBoxes runs = case nonEmpty rest of
        -- Everything fits. We are done.
        Nothing -> fitting :| []
        -- Something fits, the rest goes on the next line.
        Just runs' -> fitting <| layoutLines maxWidth openBoxes' runs'
    where
        (fitting, rest) = layoutAndWrapRunsH maxWidth openBoxes runs
        -- Update the list of open boxes using the logically last run
        -- on this line.
        openBoxes' = lastSpanBoxes $ PL.protoFragments fitting

-- | Position all the given horizontal fragments on the same line,
-- using @originY@ as its top edge, and return the bottom edge for continuation.
positionLineH
    :: Direction
    -> ParagraphAlignment
    -> Int32
    -> Int32
    -> (Int, PL.ProtoLine NonEmpty d)
    -> (Int32, NonEmpty (FragmentWithSpan d))
positionLineH dir align maxWidth originY (num, pl) = (nextY, frags)
    where
        nextY = minimum $ fmap y_min rects
        rects = fmap (\ (WithSpan _ r) -> fragmentRect r) frags
        (_, frags) = mapAccumL (positionFragmentH num) originX wpfs
        wpfs = PL.applyBoxes $ verticalAlignment originY pl
        originX = paragraphOriginX + if lineWidth > maxWidth
            then overflowingLineOffset dir (lineWidth - maxWidth)
            else fittingLineOffset align dir (maxWidth - lineWidth)
        lineWidth = PL.width pl

verticalAlignment :: Int32 -> PL.ProtoLine NonEmpty d ->
    PL.ProtoLine NonEmpty d
verticalAlignment originY pl = PL.mapFragments setOrigin pl
    where
        bottomY = originY - finalLineHeight
        finalLineHeight = fittingTop - fittingBottom

        -- Firefox-like behaviour:
        -- First extend the line upwards to fit bottom-aligned boxes,
        -- then extend the line downwards to fit top-aligned boxes.
        fittingTop = maximum $ (:) rootTop $
            map ((rootBottom +) . boxHeight) bottomAlignedBoxes
        fittingBottom = minimum $ (:) rootBottom $
            map ((fittingTop -) . boxHeight) topAlignedBoxes

        rootTop = maximum $ fmap VO.layoutTop rootVOs
        rootBottom = minimum $ fmap VO.layoutBottom rootVOs
        rootVOs = map snd $ filter underRoot $ toList vors
        rootOffset = originY - fittingTop

        boxHeight b = boxTop b - boxBottom b
        boxTop b = maximum $ map VO.layoutTop $ boxVOs b
        boxBottom b = minimum $ map VO.layoutBottom $ boxVOs b
        boxVOs b = map snd $ filter (underBox b) $ toList vors
        -- How much to shift from baseline 0 so that layoutTop = originY?
        boxTopOffset b = originY - boxTop b
        -- How much to shift from baseline 0 so that layoutBottom = bottomY?
        boxBottomOffset b = bottomY - boxBottom b

        underRoot (Nothing, _) = True
        underRoot (Just _, _) = False
        underBox _ (Nothing, _) = False
        underBox b (Just x, _) = b == x

        boxesOnLine = foldr RB.union [] $ fmap fragBoxes $ PL.protoFragments pl
        topAlignedBoxes = filter topAligned boxesOnLine
        bottomAlignedBoxes = filter bottomAligned boxesOnLine
        topAligned rb =
            boxVerticalAlignment (RB.boxOptions rb) == AlignLineTop
        bottomAligned rb =
            boxVerticalAlignment (RB.boxOptions rb) == AlignLineBottom
        fragBoxes (WithSpan rs _) = RS.spanBoxes rs
        vors = sconcat $ fmap vor $ PL.protoFragments pl
        vor (WithSpan rs pf) =
            verticalOffsetsRecursiveStruts
                (PF.direction pf)
                (RS.spanTextOptions rs)
                (RS.spanBoxes rs)

        setOrigin rs pf =
            PF.mapVerticalOffsets (VO.alignBaseline (fragOffset rs pf)) pf

        fragOffset rs pf = case NonEmpty.head (vor (WithSpan rs pf)) of
            (Nothing, vo) -> rootOffset + VO.baseline vo
            (Just b, vo) -> case boxVerticalAlignment $ RB.boxOptions b of
                AlignLineTop -> boxTopOffset b + VO.baseline vo
                AlignLineBottom -> boxBottomOffset b + VO.baseline vo
                _ -> error "verticalAlignment: wrong box used as anchor"

-- | Inline offset of the first fragment on a line that overflows.
overflowingLineOffset :: Direction -> Int32 -> Int32
overflowingLineOffset DirLTR _ = 0
overflowingLineOffset DirTTB _ = 0
overflowingLineOffset DirRTL excess = -excess
-- TODO: Check if the sign needs to be flipped for vertical text.
overflowingLineOffset DirBTT excess = -excess

-- | Inline offset of the first fragment on a line with extra blank space.
fittingLineOffset :: ParagraphAlignment -> Direction -> Int32 -> Int32
fittingLineOffset AlignLeft _ = leftAlignOffset
fittingLineOffset AlignRight _ = rightAlignOffset
fittingLineOffset AlignCentreH _ = centreAlignOffset
fittingLineOffset AlignStart DirLTR = leftAlignOffset
fittingLineOffset AlignEnd DirLTR = rightAlignOffset
fittingLineOffset AlignStart DirRTL = rightAlignOffset
fittingLineOffset AlignEnd DirRTL = leftAlignOffset
-- For completeness, treat vertical directions as horizontal directions
-- rotated 90° clockwise, thus left becomes top and right becomes bottom.
-- TODO: Verify this when vertical text is implemented.
fittingLineOffset AlignStart DirTTB = leftAlignOffset
fittingLineOffset AlignEnd DirTTB = rightAlignOffset
fittingLineOffset AlignStart DirBTT = rightAlignOffset
fittingLineOffset AlignEnd DirBTT = leftAlignOffset

leftAlignOffset :: Int32 -> Int32
leftAlignOffset _ = 0

rightAlignOffset :: Int32 -> Int32
rightAlignOffset slack = slack

centreAlignOffset :: Int32 -> Int32
centreAlignOffset slack = slack `div` 2

-- | Position the given horizontal fragment on a line, using @originX@ as its
-- left edge, returning the X coordinate of its right edge for continuation.
positionFragmentH :: Int -> Int32 -> ProtoFragmentWithBoxes d ->
    (Int32, FragmentWithSpan d)
positionFragmentH line originX (WithBoxes lbs (WithSpan rs pf) rbs) =
    (nextX, WithSpan rs frag)
    where
        nextX = contentX + contentWidth + rightSpacing
        contentX = originX + leftSpacing
        contentWidth = PF.advance pf
        leftSpacing = totalLeftSpacing bs
        rightSpacing = totalRightSpacing bs
        frag = Fragment
            { fragmentUserData = userData
            , fragmentLine = line
            , fragmentAncestorBoxes = bs
            , fragmentContentRect = contentRect
            , fragmentRect = rect
            , fragmentPen = (penX, penY)
            , fragmentGlyphs = (PF.glyphs pf)
            }
        userData = RS.spanUserData rs
        bs = ancestorBoxes lbs rbs rs
        contentRect = Rect contentX fontTop contentWidth (fontBottom - fontTop)
        rect = Rect contentX layoutTop contentWidth (layoutBottom - layoutTop)
        penX = 0
        penY = baseline - layoutTop
        VO.VerticalOffsets
            { VO.layoutTop = layoutTop
            , VO.fontTop = fontTop
            , VO.baseline = baseline
            , VO.fontBottom = fontBottom
            , VO.layoutBottom = layoutBottom
            } = PF.verticalOffsets pf

ancestorBoxes
    :: [RB.ResolvedBox d]
    -> [RB.ResolvedBox d]
    -> RS.ResolvedSpan d
    -> [AncestorBox d]
ancestorBoxes leftBoxes rightBoxes rs = map ancestorBox $ RS.spanBoxes rs
    where
        ancestorBox b = case RB.boxDirection b of
            DirLTR -> AncestorBox
                { boxUserData = RB.boxUserData b
                , boxLeftEdge = leftEdge b
                , boxRightEdge = rightEdge b
                , boxStartEdge = leftEdge b
                , boxEndEdge = rightEdge b
                }
            DirRTL -> AncestorBox
                { boxUserData = RB.boxUserData b
                , boxLeftEdge = leftEdge b
                , boxRightEdge = rightEdge b
                , boxStartEdge = rightEdge b
                , boxEndEdge = leftEdge b
                }
            _ -> AncestorBox
                { boxUserData = RB.boxUserData b
                , boxLeftEdge = NoEdge
                , boxRightEdge = NoEdge
                , boxStartEdge = NoEdge
                , boxEndEdge = NoEdge
                }
        leftEdge b = if b `elem` leftBoxes
            then SpacedEdge $ RB.boxLeftSpacing b
            else NoEdge
        rightEdge b = if b `elem` rightBoxes
            then SpacedEdge $ RB.boxRightSpacing b
            else NoEdge

-- | Calculate layout for multiple horizontal runs, breaking them as necessary
-- to fit as much content as possible without exceeding the maximum line width,
-- and return the remaining runs to be placed on other lines.
layoutAndWrapRunsH
    :: Int32
    -> [RB.ResolvedBox d]
    -> NonEmpty (WithSpan d Run)
    -> (PL.ProtoLine NonEmpty d, [WithSpan d Run])
layoutAndWrapRunsH maxWidth prevOpenBoxes runs = NonEmpty.head $ validProtoLines
    where
        validProtoLines = dropWhile1 tooLong layouts
        tooLong (pl, _) = PL.width pl > maxWidth
        layouts = fmap fstToProtoLine splits
        fstToProtoLine (runs1, runs2) =
            (protoLine prevOpenBoxes (layoutRunsH runs1) runs2, runs2)
        -- TODO: Consider optimising.
        --       We do not need to look for soft breaks further than the
        --       shortest hard break.
        -- TODO: Untrimmed whitespace should be reset to paragraph BiDi level
        --       per rule L1.
        splits = hardSplit runs :| softSplits runs

-- | Construct a `PL.ProtoLine`, peeking at the text run on the following line
-- to determine `PL.nextOpenBoxes`.
protoLine
    :: [RB.ResolvedBox d]
    -> NonEmpty (ProtoFragmentWithSpan d)
    -> [WithSpan d Run]
    -> PL.ProtoLine NonEmpty d
protoLine prev pfs rest = PL.ProtoLine pfs prev next
    where
        next = [] `fromMaybe` firstSpanBoxes rest

firstSpanBoxes :: [WithSpan d a] -> Maybe [RB.ResolvedBox d]
firstSpanBoxes xs = case xs of
    [] -> Nothing
    (WithSpan rs _) : _ -> Just $ RS.spanBoxes rs

lastSpanBoxes :: NonEmpty (WithSpan d a) -> [RB.ResolvedBox d]
lastSpanBoxes xs = case NonEmpty.last xs of
    WithSpan rs _ -> RS.spanBoxes rs

-- | Treat a list of runs as a contiguous sequence, and split them into two
-- lists so that the first list contains as many non-whitespace characters as
-- possible without crossing a hard line break (typically after a newline
-- character).
--
-- If the input is non-empty and starts with a hard line break, then the first
-- output list will contain a run of zero characters. This can be used to
-- correctly size an empty line.
--
-- If there is a hard line break in the input, the run containing it will have
-- its `runHardBreak` set to `True`.
--
-- If there is no hard line break in the input, the first output list will
-- contain the whole input, and the second output list will be empty.
hardSplit :: NonEmpty (WithSpan d Run) ->
    (NonEmpty (WithSpan d Run), [WithSpan d Run])
hardSplit runs = case reverse hSplits of
    [] -> noSplit
    (splitRuns : _) -> forcedSplit splitRuns
    where
        noSplit = (trim runs, [])
        forcedSplit (runs1, runs2) = (markHard $ trim runs1, runs2)
        markHard = mapLast markHard'
        markHard' (WithSpan rs x) = WithSpan rs x { runHardBreak = True }
        trim
            = dropWhileStartCascade isStartSpace
            . dropWhileEndCascade isEndSpace
            . dropWhileEndCascade isNewline
        -- TODO: Consider optimising.
        --       We do not need to look for any line breaks further than the
        --       shortest hard break.
        hSplits = nonEmptyFsts $
            -- from longest to shortest
            splitTextsBy (map fst . filter isHard . runLineBreaks) runs
        isHard (_, status) = status == BreakStatus.Hard

-- | Apply a function to the last element of the non-empty list.
mapLast :: (a -> a) -> NonEmpty a -> NonEmpty a
mapLast f xs = case NonEmpty.uncons xs of
    (x, Nothing) -> f x :| []
    (x, Just rest) -> NonEmpty.cons x $ mapLast f rest

-- | Treat a list of runs as a contiguous sequence,
-- and find all possible ways to split them into two non-empty lists,
-- using soft line break opportunities (typically after words) and then
-- using character boundaries.
--
-- Runs of zero characters will not be created. If line breaking would result
-- in a line that consists entirely of whitespace, this whitespace will be
-- skipped, so an empty line is not created.
--
-- The results in the form (prefix, suffix) will be ordered so that items
-- closer to the start of the list are preferred for line breaking, but without
-- considering overflows.
softSplits :: NonEmpty (WithSpan d Run) ->
    [(NonEmpty (WithSpan d Run), [WithSpan d Run])]
softSplits runs = map (allowSndEmpty . trimFst) splits
    where
        trimFst (runs1, runs2) = (trim runs1, runs2)
        trim
            = dropWhileStartCascade isStartSpace
            . dropWhileEndCascade isEndSpace
        splits = lSplits ++ cSplits
        lSplits = nonEmptyPairs $
            splitTextsBy (map fst . runLineBreaks) runs
        -- TODO: Consider optimising.
        --       We do not need to look for character breaks further than the
        --       shortest line break.
        cSplits = nonEmptyPairs $
            splitTextsBy (map fst . runCharacterBreaks) runs

-- | The suffix remaining after removing the longest prefix of the list for
-- which the predicate holds, except always including at least the last element
-- of the original list.
dropWhile1 :: (a -> Bool) -> NonEmpty a -> NonEmpty a
dropWhile1 p list = case NonEmpty.uncons list of
    (_, Nothing) -> list
    (x, Just xs) -> if p x
        then dropWhile1 p xs
        else list

-- | Calculate layout for multiple horizontal runs on the same line, without
-- any breaking.
layoutRunsH :: Functor f => f (WithSpan d Run) -> f (ProtoFragmentWithSpan d)
layoutRunsH runs = fmap layoutRunH runs

-- | Calculate layout for the given horizontal run and attach extra information.
layoutRunH :: WithSpan d Run -> ProtoFragmentWithSpan d
layoutRunH (WithSpan rs run) = WithSpan rs pf
    where
        pf = PF.protoFragmentH dir lvl vo glyphs hard
        glyphs = shapeRun (WithSpan rs run)
        dir = runDirection run
        lvl = runLevel run
        vo = verticalOffsets dir (RS.spanTextOptions rs)
        hard = runHardBreak run

-- | Vertical offsets for the given fragment, with baseline set to 0.
verticalOffsets :: Direction -> TextOptions -> VO.VerticalOffsets
verticalOffsets dir opts = VO.VerticalOffsets
    { VO.layoutTop = ascent + topHalfLeading
    , VO.fontTop = ascent
    , VO.baseline = 0
    , VO.fontBottom = - descent
    , VO.layoutBottom = - descent - bottomHalfLeading
    }
    where
        -- non-negative leading values iff `lineHeight` > `normalLineHeight`
        leading = lineHeight - normalLineHeight
        topHalfLeading = -((-leading) `div` 2)
        bottomHalfLeading = leading `div` 2
        -- `normalLineHeight` > 0 for horizontal fonts
        normalLineHeight = ascent + descent
        -- `ascent` >= 0 for horizontal fonts
        ascent = ascender extents
        -- `descent` >= 0 for horizontal fonts
        descent = - descender extents
        extents = fontExtentsForDir (textFont opts) (Just dir)
        lineHeight = case textLineHeight opts of
            Normal -> normalLineHeight
            Absolute h -> h

-- | Vertical offsets for the given fragment, aligned recursively either to
-- the root box or the nearest box with line-relative alignment, whichever is
-- closer.
--
-- Note: The font extents are calculated using the same direction for the whole
--       ancestry path regardless of the actual direction of these boxes, but
--       this should not matter for text that is only horizontal.
verticalOffsetsRecursive :: Direction -> TextOptions -> [RB.ResolvedBox d] ->
    (Maybe (RB.ResolvedBox d), VO.VerticalOffsets)
verticalOffsetsRecursive dir opts boxes = case boxes of
    [] -> -- Inline content directly in the root box.
        (Nothing, vo)
    (b : bs) -> case boxVerticalAlignment $ RB.boxOptions b of
        AlignLineTop -> (Just b, vo)
        AlignLineBottom -> (Just b, vo)
        AlignBaseline offset ->
            let parentOpts = RB.boxParentTextOptions b
                (anchor, parentVO) = verticalOffsetsRecursive dir parentOpts bs
            in (anchor, VO.alignBaseline (VO.baseline parentVO + offset) vo)
    where
        vo = verticalOffsets dir opts

-- | Like `verticalOffsetsRecursive`, but also generate struts for every
-- ancestor box.
verticalOffsetsRecursiveStruts :: Direction -> TextOptions -> [RB.ResolvedBox d]
    -> NonEmpty (Maybe (RB.ResolvedBox d), VO.VerticalOffsets)
verticalOffsetsRecursiveStruts dir opts [] =
    verticalOffsetsRecursive dir opts [] :| []
verticalOffsetsRecursiveStruts dir opts boxes@(b : bs) =
    verticalOffsetsRecursive dir opts boxes <|
    verticalOffsetsRecursiveStruts dir (RB.boxParentTextOptions b) bs

-- | Calculate layout for the given run independently of its position.
shapeRun :: WithSpan d Run -> [(GlyphInfo, GlyphPos)]
shapeRun (WithSpan rs run) = shape font buffer features
    where
        font = textFont opts
        buffer = defaultBuffer
            { text = Lazy.fromStrict $ runText run
            , contentType = Just ContentTypeUnicode
            , direction = Just $ runDirection run
            , script = runScript run
            , language = Just $ textLanguage opts
            -- Perhaps counter-intuitively, the `beginsText` and `endsText`
            -- flags refer to everything that "Data.Text.Glyphize" can see,
            -- not just the current run.
            --
            -- Since all runs are cut from a single continuous `Text` that
            -- represents the entire paragraph, and "Data.Text.Glyphize" peeks
            -- at the whole underlying byte array, HarfBuzz will be able to see
            -- both the beginning and the end of the paragraph at all times,
            -- so these flags can always be set.
            , beginsText = True
            , endsText = True
            }
        features = []
        opts = RS.spanTextOptions rs

runLineBreaks :: WithSpan d Run -> [(Int, BreakStatus.Line)]
runLineBreaks (WithSpan rs run) =
    runBreaksFromSpan run $ RS.spanLineBreaks rs

runCharacterBreaks :: WithSpan d Run -> [(Int, ())]
runCharacterBreaks (WithSpan rs run) =
    runBreaksFromSpan run $ RS.spanCharacterBreaks rs

-- | Constrain span breaks to a selected run and adjust offsets.
runBreaksFromSpan :: Run -> [(Int, a)] -> [(Int, a)]
runBreaksFromSpan run spanBreaks =
    dropWhile (not . valid) $ subOffsetsDesc (runOffsetInSpan run) spanBreaks
    where
        valid (off, _) = off <= runLength
        runLength = lengthWord8 $ getText run

-- | Predicate for characters that can be potentially removed from the
-- beginning of a line according to the CSS Text Module.
isStartSpace :: Char -> Bool
isStartSpace c = c `elem` [' ', '\t']

-- | Predicate for characters that can be potentially removed from the end of
-- a line according to the CSS Text Module.
isEndSpace :: Char -> Bool
isEndSpace c = c `elem` [' ', '\t', '\x1680']

-- | Predicate for characters that should be removed from the end of a line in
-- the case of a hard line break.
isNewline :: Char -> Bool
isNewline c = c == '\n'