~jaro/balkon

0680c59bcaa7239488d49b6bc9ed0aa8ae0ec3b4 — Jaro 11 months ago 2d06bc9
Consolidate tree types into one.
M balkon.cabal => balkon.cabal +0 -1
@@ 129,7 129,6 @@ library balkon-internal
        Data.Text.ParagraphLayout.Internal.TextContainer,
        Data.Text.ParagraphLayout.Internal.TextOptions,
        Data.Text.ParagraphLayout.Internal.Tree,
        Data.Text.ParagraphLayout.Internal.TreeOfTexts,
        Data.Text.ParagraphLayout.Internal.WithSpan,
        Data.Text.ParagraphLayout.Internal.Zipper


M src/Data/Text/ParagraphLayout/Internal/Plain.hs => src/Data/Text/ParagraphLayout/Internal/Plain.hs +1 -1
@@ 47,7 47,7 @@ plainToRich (P.Paragraph arr off spans opts) = R.Paragraph arr off rootNode opts
-- | 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, d)
boxFromPlain :: TextOptions -> Int -> Span d -> Box Int (Int, d)
boxFromPlain baseOpts i s = Box [TextSequence (i, spanUserData s) len] opts
    where
        len = spanLength s

M src/Data/Text/ParagraphLayout/Internal/Rich/Paragraph.hs => src/Data/Text/ParagraphLayout/Internal/Rich/Paragraph.hs +3 -4
@@ 12,7 12,6 @@ import qualified Data.List.NonEmpty as NonEmpty
import Data.Text.Array (Array)
import Data.Text.Internal (Text (Text))

import qualified Data.Text.ParagraphLayout.Internal.TreeOfTexts as Texts
import Data.Text.ParagraphLayout.Internal.ParagraphOptions
import Data.Text.ParagraphLayout.Internal.Tree



@@ 42,7 41,7 @@ data Paragraph d = Paragraph
    -- Any characters preceding this offset will not be shaped, but may still
    -- be used to influence the shape of neighbouring characters.

    (RootNode d)
    (RootNode Int d)
    -- ^ Parts of the text to be laid out, represented as a tree.
    -- The in-order walk of this tree corresponds to the logical order
    -- of the text.


@@ 50,13 49,13 @@ data Paragraph d = Paragraph
    ParagraphOptions
    -- ^ Options applying to the paragraph as a whole.

constructParagraph :: Text -> Texts.RootNode d -> Text -> ParagraphOptions ->
constructParagraph :: Text -> RootNode Text d -> Text -> ParagraphOptions ->
    Paragraph d
constructParagraph prefix root suffix = Paragraph arr afterPrefix root'
    where
        (Text arr beforePrefix _) = txt
        afterPrefix = beforePrefix + prefixLen
        (txt, prefixLen, root') = Texts.toStrict prefix root suffix
        (txt, prefixLen, root') = glue prefix root suffix

-- | Calculate the offsets into the `Paragraph`'s underlying `Data.Text.Array`
-- where each text node starts and ends, in ascending order. The resulting list

M src/Data/Text/ParagraphLayout/Internal/Tree.hs => src/Data/Text/ParagraphLayout/Internal/Tree.hs +76 -18
@@ 2,38 2,56 @@
--
-- The tree is a hierarchy of boxes, with one box always present as the root.
-- Each box may contain any combination of text sequences and other boxes.
--
-- The type parameter @t@ refers to the way in which text is represented in the
-- tree:
--
-- - `Text` means that each leaf node directly contains its own text.
-- - `Int` means that the text comes from a contiguous byte array, and each
--   leaf node specifies only the number of bytes belonging to its text.
--
-- The `glue` function can be used to convert a `Text` tree into an `Int` tree.
--
-- The type parameter @d@ defines the type of user data to be associated with
-- each non-root node.
module Data.Text.ParagraphLayout.Internal.Tree
    ( RootNode (..)
    , InnerNode (..)
    , Box (..)
    , Leaf (..)
    , flatten
    , glue
    )
where

import Data.Text (Text)
import Data.Text.Foreign (lengthWord8)
import qualified Data.Text.Lazy as Lazy (toStrict)
import qualified Data.Text.Internal.Lazy as Lazy (Text, chunk, empty)

import Data.Text.ParagraphLayout.Internal.BoxOptions
import Data.Text.ParagraphLayout.Internal.ResolvedBox
import Data.Text.ParagraphLayout.Internal.TextOptions

-- | Root of the paragraph tree.
data RootNode d
data RootNode t d

    = RootBox
    -- ^ The root inline box. Always present in a paragraph.
    --
    -- Cannot be styled directly, but can still set options for formatting
    -- text sequences directly descending from this box.
        (Box d)
        (Box t d)
        -- ^ Contents of the box.

-- | Non-root node of the paragraph tree.
data InnerNode d
data InnerNode t d

    = InlineBox
    -- ^ An inline box, nested in another box.
        d
        -- ^ User-defined data associated with the box.
        (Box d)
        (Box t d)
        -- ^ Contents of the box.
        BoxOptions
        -- ^ Style options to apply to the inline box.


@@ 42,13 60,13 @@ data InnerNode d
    -- ^ A leaf node containing text.
        d
        -- ^ User-defined data associated with the text node.
        Int
        -- ^ Byte offset to the next text node or the end of the paragraph text.
        t
        -- ^ Representation of the text contained by the text node.

-- | A box with content and a defined format. Corresponds to a DOM element.
data Box d = Box
data Box t d = Box

    [InnerNode d]
    [InnerNode t d]
    -- ^ Text nodes and other boxes contained by this box.

    TextOptions


@@ 59,13 77,13 @@ data Box d = Box
type BoxPath d = [ResolvedBox d]

-- | Representation of a leaf node of the tree after flattening.
data Leaf d = TextLeaf
data Leaf t d = TextLeaf

    d
    -- ^ User-defined data associated with the text node.

    Int
    -- ^ Byte offset to the next text node or the end of the paragraph text.
    t
    -- ^ Representation of the text contained by the text node.

    TextOptions
    -- ^ Style options to apply to this text sequence.


@@ 75,22 93,62 @@ data Leaf d = TextLeaf
    -- of the original tree.

-- | Convert the tree to a flat list of its leaf nodes (text sequences).
flatten :: RootNode d -> [Leaf d]
flatten :: RootNode t d -> [Leaf t d]
flatten (RootBox (Box ns textOpts)) = snd $ flattenNodes 0 [] textOpts ns

flattenNodes :: Int -> BoxPath d -> TextOptions -> [InnerNode d] ->
    (Int, [Leaf d])
flattenNodes :: Int -> BoxPath d -> TextOptions -> [InnerNode t d] ->
    (Int, [Leaf t d])
flattenNodes idx _ _ [] = (idx, [])
flattenNodes idx path textOpts (n : ns) = (idx'', flat1 ++ flat2)
    where
        (idx', flat1) = flattenNode idx path textOpts n
        (idx'', flat2) = flattenNodes idx' path textOpts ns

flattenNode :: Int -> BoxPath d -> TextOptions -> InnerNode d ->
    (Int, [Leaf d])
flattenNode idx path textOpts (TextSequence d len) =
    (idx, [TextLeaf d len textOpts path])
flattenNode :: Int -> BoxPath d -> TextOptions -> InnerNode t d ->
    (Int, [Leaf t d])
flattenNode idx path textOpts (TextSequence d t) =
    (idx, [TextLeaf d t textOpts path])
flattenNode idx path _ (InlineBox d (Box ns textOpts) boxOpts) =
    flattenNodes (idx + 1) (ResolvedBox d idx boxOpts dir : path) textOpts ns
    where
        dir = textDirection textOpts

-- | Concatenate all pieces of text from a `Text` tree, plus an optional prefix
-- and suffix, into a contiguous `Text` and build an `Int` tree with
-- corresponding byte lengths.
--
-- Using a contiguous `Text` lets HarfBuzz take neighbouring characters into
-- consideration when making shaping decisions, so that for example kerning
-- does not stop working on node boundaries.
glue :: Text -> RootNode Text d -> Text -> (Text, Int, RootNode Int d)
glue prefix root suffix = (txt, initialOffset, root')
    where
        txt = Lazy.toStrict $ Lazy.chunk prefix txtTail
        initialOffset = lengthWord8 prefix
        (txtTail, root') = glueRoot (Lazy.chunk suffix Lazy.empty) root

glueRoot :: Lazy.Text -> RootNode Text d -> (Lazy.Text, RootNode Int d)
glueRoot t (RootBox b) = (t', RootBox b')
    where
        (t', b') = glueBox t b

glueBox :: Lazy.Text -> Box Text d -> (Lazy.Text, Box Int d)
glueBox t (Box nodes opts) = (t', Box nodes' opts)
    where
        (t', nodes') = glueNodes t nodes

glueNodes :: Lazy.Text -> [InnerNode Text d] -> (Lazy.Text, [InnerNode Int d])
glueNodes t [] = (t, [])
glueNodes t (node : nodes) = (t'', node' : nodes')
    where
        (t'', node') = glueNode t' node
        (t', nodes') = glueNodes t nodes

glueNode :: Lazy.Text -> InnerNode Text d -> (Lazy.Text, InnerNode Int d)
glueNode suffix (TextSequence d txt) = (combinedText, node)
    where
        combinedText = Lazy.chunk txt suffix
        node = TextSequence d (lengthWord8 txt)
glueNode suffix (InlineBox d b o) = (combinedText, InlineBox d node o)
    where
        (combinedText, node) = glueBox suffix b

D src/Data/Text/ParagraphLayout/Internal/TreeOfTexts.hs => src/Data/Text/ParagraphLayout/Internal/TreeOfTexts.hs +0 -88
@@ 1,88 0,0 @@
-- | Represents the contents of a paragraph as a tree of boxes and texts.
--
-- This is intended for easier construction of paragraphs, at the cost of lower
-- performance. All texts will be concatenated together by layout functions.
module Data.Text.ParagraphLayout.Internal.TreeOfTexts
    ( RootNode (..)
    , InnerNode (..)
    , Box (..)
    , toStrict
    )
where

import Data.Text (Text)
import Data.Text.Foreign (lengthWord8)
import qualified Data.Text.Lazy as Lazy (toStrict)
import qualified Data.Text.Internal.Lazy as Lazy (Text, chunk, empty)

import Data.Text.ParagraphLayout.Internal.BoxOptions
import Data.Text.ParagraphLayout.Internal.TextOptions
import qualified Data.Text.ParagraphLayout.Internal.Tree as Strict

-- | Root of the paragraph tree.
data RootNode d

    = RootBox (Box d)
    -- ^ The root box.

-- | Non-root node of the paragraph tree.
data InnerNode d

    = InlineBox
    -- ^ An inline box, nested in another box.
        d
        -- ^ User-defined data associated with the box.
        (Box d)
        -- ^ Contents of the box.
        BoxOptions
        -- ^ Style options to apply to the inline box.

    | TextSequence
    -- ^ A leaf node containing text.
        d
        -- ^ User-defined data associated with the text node.
        Text
        -- ^ Text contents of the node.

-- | A box with content and a defined format. Corresponds to a DOM element.
data Box d = Box

    [InnerNode d]
    -- ^ Text nodes and other boxes contained by this box.

    TextOptions
    -- ^ Style options to apply to text sequences directly contained
    -- by this box.

toStrict :: Text -> RootNode d -> Text -> (Text, Int, Strict.RootNode d)
toStrict prefix root suffix = (txt, initialOffset, root')
    where
        txt = Lazy.toStrict $ Lazy.chunk prefix txtTail
        initialOffset = lengthWord8 prefix
        (txtTail, root') = strictRoot (Lazy.chunk suffix Lazy.empty) root

strictRoot :: Lazy.Text -> RootNode d -> (Lazy.Text, Strict.RootNode d)
strictRoot t (RootBox b) = (t', Strict.RootBox b')
    where
        (t', b') = strictBox t b

strictBox :: Lazy.Text -> Box d -> (Lazy.Text, Strict.Box d)
strictBox t (Box nodes opts) = (t', Strict.Box nodes' opts)
    where
        (t', nodes') = strictNodes t nodes

strictNodes :: Lazy.Text -> [InnerNode d] -> (Lazy.Text, [Strict.InnerNode d])
strictNodes t [] = (t, [])
strictNodes t (node : nodes) = (t'', node' : nodes')
    where
        (t'', node') = strictNode t' node
        (t', nodes') = strictNodes t nodes

strictNode :: Lazy.Text -> InnerNode d -> (Lazy.Text, Strict.InnerNode d)
strictNode suffix (TextSequence d txt) = (combinedText, node)
    where
        combinedText = Lazy.chunk txt suffix
        node = Strict.TextSequence d (lengthWord8 txt)
strictNode suffix (InlineBox d b o) = (combinedText, Strict.InlineBox d node o)
    where
        (combinedText, node) = strictBox suffix b

M test/Data/Text/ParagraphLayout/Internal/TreeSpec.hs => test/Data/Text/ParagraphLayout/Internal/TreeSpec.hs +6 -6
@@ 9,7 9,7 @@ import Data.Text.ParagraphLayout.Internal.Tree
t :: TextOptions
t = defaultTextOptions undefined

complexTree :: RootNode String
complexTree :: RootNode Int String
complexTree = RootBox $ Box
    [ TextSequence "a" 1
    , InlineBox


@@ 83,19 83,19 @@ complexTree = RootBox $ Box
    ]
    t

leafData :: Leaf d -> d
leafData :: Leaf t d -> d
leafData (TextLeaf d _ _ _) = d

leafPath :: Leaf d -> [ResolvedBox d]
leafPath :: Leaf t d -> [ResolvedBox d]
leafPath (TextLeaf _ _ _ path) = path

leafDepth :: Leaf d -> Int
leafDepth :: Leaf t d -> Int
leafDepth = length . leafPath

leafPathData :: Leaf d -> [d]
leafPathData :: Leaf t d -> [d]
leafPathData = map boxUserData . leafPath

leafPathIndexes :: Leaf d -> [Int]
leafPathIndexes :: Leaf t d -> [Int]
leafPathIndexes = map boxIndex . leafPath

spec :: Spec

M test/Data/Text/ParagraphLayout/Rich/ParagraphData.hs => test/Data/Text/ParagraphLayout/Rich/ParagraphData.hs +5 -5
@@ 10,14 10,14 @@ module Data.Text.ParagraphLayout.Rich.ParagraphData
where

import Data.Int (Int32)
import Data.Text (pack)
import Data.Text (Text, pack)
import Data.Text.Glyphize (Direction (DirLTR, DirRTL), Font)

import Data.Text.ParagraphLayout.Internal.BoxOptions
import Data.Text.ParagraphLayout.Internal.ParagraphOptions
import Data.Text.ParagraphLayout.Internal.Rich.Paragraph
import Data.Text.ParagraphLayout.Internal.TextOptions
import Data.Text.ParagraphLayout.Internal.TreeOfTexts
import Data.Text.ParagraphLayout.Internal.Tree

tLTR :: TextOptions
tLTR = defaultTextOptions DirLTR


@@ 28,13 28,13 @@ tRTL = defaultTextOptions DirRTL
b_ :: BoxOptions
b_ = defaultBoxOptions

rootBox :: TextOptions -> [InnerNode d] -> RootNode d
rootBox :: TextOptions -> [InnerNode Text d] -> RootNode Text d
rootBox opts nodes = RootBox (Box nodes opts)

box :: d -> BoxOptions -> TextOptions -> [InnerNode d] -> InnerNode d
box :: d -> BoxOptions -> TextOptions -> [InnerNode Text d] -> InnerNode Text d
box label boxOpts textOpts nodes = InlineBox label (Box nodes textOpts) boxOpts

text :: d -> String -> InnerNode d
text :: d -> String -> InnerNode Text d
text label contents = TextSequence label (pack contents)

hardBoxBreakLTRParagraph :: Font -> ParagraphOptions -> Paragraph String