cattrap-0.6.0.0: Lays out boxes according to the CSS Box Model.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.Layout.Inline

Description

Sizes inline text & extracts positioned children, wraps Balkón for the actual logic.

Synopsis

Documentation

paragraphMap :: (b -> b') -> Paragraph (a, b, c) -> Paragraph (a, b', c) Source #

Apply an operation to the 2nd field of the paragraph's userdata, for it's entire subtree.

layoutMap :: (b -> b') -> ParagraphLayout (a, b, c) -> ParagraphLayout (a, b', c) Source #

Apply an operation to the 2nd field of a laid-out paragraph's userdata, for it's entire subtree.

treeMap :: (b -> b') -> FragmentTree (a, b, c) -> FragmentTree (a, b', c) Source #

Apply an operation to the 2nd field of the tree extracted from a laid-out paragraph, for all nodes.

inlineMin :: (CastDouble x, CastDouble y) => (z -> PaddedBox x y) -> Paragraph (a, Either (PaddedBox x y) z, c) -> Size x y Source #

Compute minimum width & height for some richtext.

inlineSize :: (CastDouble x, CastDouble y) => (z -> PaddedBox x y) -> Paragraph (a, Either (PaddedBox x y) z, c) -> Size x y Source #

Compute width & height of some richtext at configured width.

inlineChildren :: (CastDouble x, CastDouble y, Eq x, Eq y, Eq a, Eq c, Eq z) => (z -> PaddedBox x y) -> Paragraph (a, Either (PaddedBox x y) z, c) -> [FragmentTree (a, Either (PaddedBox x y) z, c)] Source #

Retrieve children out of some richtext, associating given userdata with them.

layoutSize :: (CastDouble x, CastDouble y) => ParagraphLayout a -> Size x y Source #

Retrieve a laid-out paragraph's rect & convert to CatTrap types.

layoutChildren :: Eq a => ParagraphLayout a -> [FragmentTree a] Source #

Retrieve a laid-out paragraph's children & associate with given userdata.

treeBox :: (CastDouble m, CastDouble n) => FragmentTree (a, PaddedBox m n, c) -> PaddedBox m n Source #

Compute the paddedbox for a subtree.

positionTree :: (Double, Double) -> ((Double, Double) -> b -> b') -> FragmentTree (a, b, c) -> FragmentTree (a, b', ((Double, Double), c)) Source #

Add an X,Y offset to all positions, annotating the userdata.

treeInner :: FragmentTree (a, b, c) -> c Source #

Retrieve 3rd userdata field.

treeInner' :: FragmentTree a -> a Source #

Retrieve userdata field.

glyphs :: FragmentTree x -> [(GlyphInfo, GlyphPos)] Source #

Retrieve Harfbuzz data out of the tree extracted from Balkón.

codepoints :: FragmentTree x -> [Word32] Source #

Retrieve the Unicode codepoints out of the tree extracted from Balkón.

data FragmentTree x Source #

A tree extracted from Balkón's inline layout.

Constructors

Branch (AncestorBox x) [FragmentTree x] 
Leaf (Fragment x) 

Instances

Instances details
Show x => Show (FragmentTree x) Source # 
Instance details

Defined in Graphics.Layout.Inline

Eq x => Eq (FragmentTree x) Source # 
Instance details

Defined in Graphics.Layout.Inline