-- | Legacy plain text layout interface.
module Data.Text.ParagraphLayout.Internal.Plain (layoutPlain)
where
import Data.Text.Glyphize (Direction (DirLTR))
import Data.Text.ParagraphLayout.Internal.AncestorBox
import Data.Text.ParagraphLayout.Internal.BiDiLevels
import Data.Text.ParagraphLayout.Internal.BoxOptions
import Data.Text.ParagraphLayout.Internal.Fragment
import Data.Text.ParagraphLayout.Internal.ParagraphOptions
import qualified Data.Text.ParagraphLayout.Internal.Plain.Paragraph as P
import qualified Data.Text.ParagraphLayout.Internal.Plain.ParagraphLayout as P
import Data.Text.ParagraphLayout.Internal.Rich (layoutRich)
import qualified Data.Text.ParagraphLayout.Internal.Rich.Paragraph as R
import qualified Data.Text.ParagraphLayout.Internal.Rich.ParagraphLayout as R
import Data.Text.ParagraphLayout.Internal.Span
import Data.Text.ParagraphLayout.Internal.TextOptions
import Data.Text.ParagraphLayout.Internal.Tree
-- | Lay out a paragraph of plain text using a single font.
layoutPlain :: P.Paragraph d -> P.ParagraphLayout d
layoutPlain p@(P.Paragraph _ _ spans _) =
richLayoutToPlain (length spans) $ layoutRich $ plainToRich p
-- | Convert a legacy plain text paragraph to a rich text paragraph.
--
-- Each plain text span is converted to a box with one text node inside.
--
-- Span indexes are added to the user data internally, then used to split the
-- resulting fragments according to their corresponding spans.
plainToRich :: P.Paragraph d -> R.Paragraph (Int, d)
plainToRich p@(P.Paragraph arr off spans opts) =
R.Paragraph arr off rootNode opts
where
rootNode = RootBox rootBox
rootBox = Box spanNodes baseOpts
spanNodes = map spanNode indexedSpans
spanNode (i, s) = InlineBox
(i, spanUserData s)
(boxFromPlain baseOpts i s)
defaultBoxOptions
indexedSpans = zip [0 ..] spans
baseOpts = (defaultTextOptions $ detectDirection p)
{ textFont = paragraphFont opts
, textLineHeight = paragraphLineHeight opts
}
-- | Simplified autodetection of text direction for plain text,
-- to provide temporary compatibility with the old interface which
-- did not allow setting text direction explicitly.
--
-- Note that the detected direction carries over hard line breaks,
-- which is not compliant with the Unicode Bidirectional Algorithm.
detectDirection :: P.Paragraph d -> Direction
detectDirection p = case firstStrongDirection (P.paragraphText p) of
Just dir -> dir
Nothing -> DirLTR
-- | Convert a legacy `Span` to a rich text box with one text node inside.
--
-- Add the given index to the user data, so that it can be extracted later.
boxFromPlain :: TextOptions -> Int -> Span d -> Box Int (Int, d)
boxFromPlain baseOpts i s = Box [TextSequence (i, spanUserData s) len] opts
where
len = spanLength s
opts = baseOpts { textLanguage = spanLanguage $ spanOptions s }
-- | Convert a rich paragraph layout with span indexes into the legacy paragraph
-- layout with an array of spans.
richLayoutToPlain :: Int -> R.ParagraphLayout (Int, d) -> P.ParagraphLayout d
richLayoutToPlain numSpans pl = P.paragraphLayout sls
where
sls = map SpanLayout fragsBySpan
fragsBySpan = take numSpans $ splitBySpanIndex frags
frags = R.paragraphFragments pl
splitBySpanIndex :: [Fragment (Int, d)] -> [[Fragment d]]
splitBySpanIndex frags = [getBySpanIndex i frags | i <- [0 ..]]
getBySpanIndex :: Int -> [Fragment (Int, d)] -> [Fragment d]
getBySpanIndex idx = map stripSpanIndex . filter ((== idx) . getSpanIndex)
getSpanIndex :: Fragment (Int, d) -> Int
getSpanIndex Fragment { fragmentUserData = (i, _) } = i
stripSpanIndex :: Fragment (Int, d) -> Fragment d
stripSpanIndex f = f
{ fragmentUserData = snd (fragmentUserData f)
, fragmentAncestorBoxes = map stripSpanIndexInBox (fragmentAncestorBoxes f)
}
stripSpanIndexInBox :: AncestorBox (Int, d) -> AncestorBox d
stripSpanIndexInBox ab = ab { boxUserData = snd (boxUserData ab) }