@@ 2,10 2,12 @@ module Data.Text.ParagraphLayout.Internal.Plain (layoutPlain)
where
import Control.Applicative (ZipList (ZipList), getZipList)
+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 (catMaybes)
import Data.Text.Foreign (lengthWord8)
import Data.Text.Glyphize
( Buffer (..)
@@ 66,23 68,26 @@ spanToRunsWrapped s = map (WithSpan s) (spanToRuns s)
layoutAndAlignLines :: Int32 -> NonEmpty (WithSpan Run) -> [WithSpan Fragment]
layoutAndAlignLines maxWidth runs = frags
where
- frags = concat fragsInLines
+ frags = concatMap NonEmpty.toList fragsInLines
(_, fragsInLines) = mapAccumL positionLineH originY canonicalLines
canonicalLines = fmap canonicalOrder logicalLines
- logicalLines = NonEmpty.filter (not . null) $ layoutLines maxWidth runs
+ logicalLines = nonEmptyItems $ layoutLines maxWidth runs
originY = paragraphOriginY
+nonEmptyItems :: Foldable t => t [a] -> [NonEmpty a]
+nonEmptyItems = catMaybes . map nonEmpty . toList
+
-- | Reorder the given fragments from logical order to whatever order HarfBuzz
-- uses (LTR for horizontal text, TTB for vertical text), so that cluster order
-- is preserved even across runs.
-canonicalOrder :: [WithSpan PF.ProtoFragment] -> [WithSpan PF.ProtoFragment]
-canonicalOrder [] = []
-canonicalOrder pfs@((WithSpan _ headPF) : _) = case PF.direction headPF of
+canonicalOrder :: NonEmpty (WithSpan PF.ProtoFragment) ->
+ NonEmpty (WithSpan PF.ProtoFragment)
+canonicalOrder pfs@((WithSpan _ headPF) :| _) = case PF.direction headPF of
-- TODO: Use BiDi levels to control reversing.
Just DirLTR -> pfs
- Just DirRTL -> reverse pfs
+ Just DirRTL -> NonEmpty.reverse pfs
Just DirTTB -> pfs
- Just DirBTT -> reverse pfs
+ Just DirBTT -> NonEmpty.reverse pfs
-- If no guess can be made, use LTR.
-- TODO: Add explicit direction to input interface.
Nothing -> pfs
@@ 111,16 116,13 @@ layoutLines maxWidth runs = case nonEmpty rest of
-- @vertical-align: top@ in CSS.
--
-- TODO: For rich text, allow other types of vertical alignment.
-positionLineH :: Int32 -> [WithSpan PF.ProtoFragment] ->
- (Int32, [WithSpan Fragment])
+positionLineH :: Int32 -> NonEmpty (WithSpan PF.ProtoFragment) ->
+ (Int32, NonEmpty (WithSpan Fragment))
positionLineH originY pfs = (nextY, frags)
where
- -- A line with no fragments will be considered to have zero height.
- -- This can happen when line breaking produces a line that contains
- -- only spaces.
- nextY = if null rects then originY else maximum $ map y_min rects
- rects = map (\ (WithSpan _ r) -> fragmentRect r) frags
- frags = snd $ mapAccumL (positionFragmentH originY) originX pfs
+ nextY = maximum $ fmap y_min rects
+ rects = fmap (\ (WithSpan _ r) -> fragmentRect r) frags
+ (_, frags) = mapAccumL (positionFragmentH originY) originX pfs
originX = paragraphOriginX
-- | Position the given horizontal fragment on a line,