~alcinnz/CatTrap

ref: 2fe0db0f29a37143ccd694ce1aa8912b26f18408 CatTrap/Graphics/Layout/Inline.hs -rw-r--r-- 9.1 KiB
2fe0db0f — Adrian Cochrane Handle property on containing blocks. 1 year, 3 months ago
                                                                                
f5fbeaa6 Adrian Cochrane
49365312 Adrian Cochrane
9db95983 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
b07f5dcb Adrian Cochrane
e8a4642a Adrian Cochrane
d4a87f66 Adrian Cochrane
8308c7a9 Adrian Cochrane
9db95983 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
59a70cdb Adrian Cochrane
d4a87f66 Adrian Cochrane
9db95983 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
db049add Adrian Cochrane
59a70cdb Adrian Cochrane
b07f5dcb Adrian Cochrane
db049add Adrian Cochrane
b07f5dcb Adrian Cochrane
d4a87f66 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
db049add Adrian Cochrane
d4a87f66 Adrian Cochrane
b07f5dcb Adrian Cochrane
db049add Adrian Cochrane
9db95983 Adrian Cochrane
db049add Adrian Cochrane
9db95983 Adrian Cochrane
85d144a0 Adrian Cochrane
db049add Adrian Cochrane
b07f5dcb Adrian Cochrane
85d144a0 Adrian Cochrane
db049add Adrian Cochrane
e8a4642a Adrian Cochrane
f5fbeaa6 Adrian Cochrane
db049add Adrian Cochrane
d4a87f66 Adrian Cochrane
9db95983 Adrian Cochrane
d4a87f66 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
9db95983 Adrian Cochrane
59a70cdb Adrian Cochrane
db049add Adrian Cochrane
15a1fd94 Adrian Cochrane
59a70cdb Adrian Cochrane
8308c7a9 Adrian Cochrane
15a1fd94 Adrian Cochrane
59a70cdb Adrian Cochrane
8308c7a9 Adrian Cochrane
d4a87f66 Adrian Cochrane
db049add Adrian Cochrane
59a70cdb Adrian Cochrane
f5fbeaa6 Adrian Cochrane
db049add Adrian Cochrane
b07f5dcb Adrian Cochrane
8308c7a9 Adrian Cochrane
f5fbeaa6 Adrian Cochrane
b07f5dcb Adrian Cochrane
e8a4642a Adrian Cochrane
8308c7a9 Adrian Cochrane
e8a4642a Adrian Cochrane
8308c7a9 Adrian Cochrane
e8a4642a Adrian Cochrane
9db95983 Adrian Cochrane
59a70cdb Adrian Cochrane
9db95983 Adrian Cochrane
e8a4642a Adrian Cochrane
9db95983 Adrian Cochrane
15a1fd94 Adrian Cochrane
9db95983 Adrian Cochrane
e8a4642a Adrian Cochrane
15a1fd94 Adrian Cochrane
9db95983 Adrian Cochrane
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
{-# LANGUAGE TupleSections #-}
-- | Sizes inline text & extracts positioned children,
-- wraps Balkón for the actual logic.
module Graphics.Layout.Inline(paragraphMap, layoutMap, treeMap,
    inlineMin, inlineSize, inlineChildren, layoutSize, layoutChildren,
    treeBox, positionTree, treeInner, FragmentTree(..)) where

import Data.Text.ParagraphLayout.Rich (Paragraph(..), ParagraphOptions(..),
                                Fragment(..), ParagraphLayout(..), AncestorBox(..),
                                InnerNode(..), Box(..), RootNode(..),
                                layoutRich, boxSpacing, BoxSpacing(..))
import Data.Text.ParagraphLayout.Rect (Rect(..),
                                width, height, x_max, x_min, y_min, y_max)
import Data.Int (Int32)

import Graphics.Layout.Box hiding (min, max, width, height)
import qualified Graphics.Layout.Box as Box
import Graphics.Layout.CSS.Font (hbUnit)

-- | Convert from Harfbuzz units to device pixels as a Double
hbScale :: Int32 -> Double
hbScale = (/hbUnit) . fromIntegral
-- | Convert from Harfbuzz units to device pixels as a Double or Length.
c :: CastDouble a => Int32 -> a
c = fromDouble . hbScale
-- | Convert from a CastDouble in device pixels to Harfbuzz units.
unscale :: CastDouble x => x -> Int32
unscale = floor . (*hbUnit) . toDouble

-- | Compute minimum width & height for some richtext.
inlineMin :: (CastDouble x, CastDouble y) =>
        Paragraph (a, PaddedBox x y, c) -> Size x y
inlineMin self = Size (c $ width rect) (c $ height rect)
    where rect = layoutRich' self 0
-- | Compute width & height of some richtext at configured width.
inlineSize :: (CastDouble x, CastDouble y) =>
        Paragraph (a, PaddedBox x y, c) -> Size x y
inlineSize self = layoutSize $ layoutRich $ lowerSpacing self
-- | Retrieve children out of some richtext,
-- associating given userdata with them.
inlineChildren :: (CastDouble x, CastDouble y, Eq x, Eq y, Eq a, Eq c) =>
        Paragraph (a, PaddedBox x y, c) -> [FragmentTree (a, PaddedBox x y, c)]
inlineChildren self = layoutChildren $ layoutRich $ lowerSpacing self

-- | Retrieve a laid-out paragraph's rect & convert to CatTrap types.
layoutSize :: (CastDouble x, CastDouble y) => ParagraphLayout a -> Size x y
layoutSize self = Size (c $ width r) (c $ height r)
  where r = paragraphRect self
-- | Retrieve a laid-out paragraph's children & associate with given userdata.
layoutChildren :: Eq a => ParagraphLayout a -> [FragmentTree a]
layoutChildren self = reconstructTree self

-- | Layout a paragraph at given width & retrieve resulting rect.
layoutRich' :: (CastDouble m, CastDouble n) =>
        Paragraph (a, PaddedBox m n, c) -> Int32 -> Rect Int32
layoutRich' (Paragraph a b c d) width = paragraphRect $ layoutRich $
    lowerSpacing $ Paragraph a b c d { paragraphMaxWidth = width }

-- | Copy surrounding whitespace into Balkon properties.
lowerSpacing :: (CastDouble m, CastDouble n) =>
    Paragraph (a, PaddedBox m n, c) -> Paragraph (a, PaddedBox m n, c)
lowerSpacing (Paragraph a b (RootBox c) d) = Paragraph a b (RootBox $ inner c) d
  where
    inner (Box childs opts) = flip Box opts $ map inner' childs
    inner' (InlineBox e@(_, f, _) child opts) = InlineBox e (inner child) opts {
            boxSpacing = BoxSpacingLeftRight (leftSpace box) (rightSpace box)
        }
      where box = mapX' unscale $ mapY' unscale f
    inner' self@(TextSequence _ _) = self


data FragmentTree x = Branch (AncestorBox x) [FragmentTree x]
    | Leaf (Fragment x)

-- | Apply an operation to the 2nd field of the paragraph's userdata,
-- for it's entire subtree.
paragraphMap :: (b -> b') -> Paragraph (a, b, c) -> Paragraph (a, b', c)
paragraphMap cb (Paragraph a b (RootBox c) d) =
    Paragraph a b (RootBox $ inner c) d
  where
    inner (Box childs opts) = flip Box opts $ map inner' childs
    inner' (InlineBox (e, f, g) child opts) =
        InlineBox (e, cb f, g) (inner child) opts
    inner' (TextSequence (e, f, g) leaf) = TextSequence (e, cb f, g) leaf

-- | Apply an operation to the 2nd field of a laid-out paragraph's userdata,
-- for it's entire subtree.
layoutMap :: (b -> b') -> ParagraphLayout (a, b, c) -> ParagraphLayout (a, b', c)
layoutMap cb (ParagraphLayout a b) = ParagraphLayout a $ map inner b
  where
    inner self@Fragment { fragmentUserData = (a, b, c) } = self {
        fragmentUserData = (a, cb b, c),
        fragmentAncestorBoxes = map inner' $ fragmentAncestorBoxes self
      }
    inner' self@AncestorBox { boxUserData = (a, b, c) } = self {
        boxUserData = (a, cb b, c)
      }

-- | Apply an operation to the 2nd field of the tree extracted from a laid-out
-- paragraph, for all nodes.
treeMap :: (b -> b') -> FragmentTree (a, b, c) -> FragmentTree (a, b', c)
treeMap cb (Branch self@AncestorBox { boxUserData = (a, b, c) } childs) =
    Branch self { boxUserData = (a, cb b, c) } $ map (treeMap cb) childs
treeMap cb (Leaf self@Fragment { fragmentUserData = (a, b, c) }) =
    Leaf self { fragmentUserData = (a, cb b, c), fragmentAncestorBoxes = [] }

-- | Retrieve the rect for a fragment & convert to CatTrap types.
fragmentSize :: (CastDouble x, CastDouble y) =>
        FragmentTree (a, PaddedBox x y, c) -> Size x y
fragmentSize self = Size (c $ width r) (c $ height r)
    where r = treeRect self
-- | Compute the unioned rect for a subtree.
treeRect :: (CastDouble m, CastDouble n) =>
        FragmentTree (a, PaddedBox m n, c) -> Rect Int32
treeRect (Branch AncestorBox { boxUserData = (_, box', _)} childs) =
        foldr unionRect (Rect 0 0 0 0) $ map treeRect childs
    where
        unionRect a b = Rect
            (x_min a `min` x_min b - leftSpace box)
            (y_min a `min` y_min b - topSpace box)
            (x_max a `max` x_max b - x_min a `min` x_min b + hSpace box)
            (y_max a `max` y_max b - y_min a `min` x_min b + vSpace box)
        box :: PaddedBox Int32 Int32
        box = mapX' unscale $ mapY' unscale box'
treeRect (Leaf self) = fragmentRect self

-- | Compute the paddedbox for a subtree.
treeBox :: (CastDouble m, CastDouble n) =>
    FragmentTree (a, PaddedBox m n, c) -> PaddedBox m n
treeBox self@(Branch AncestorBox { boxUserData = (_, box', _)} _) = box' {
    Box.min = size', Box.max = size', Box.size = size', Box.nat = size
  } where
    size' = mapSizeX fromDouble $ mapSizeY fromDouble size
    size = mapSizeX (subtract $ hSpace box) $ mapSizeY (subtract $ vSpace box)$
         mapSizeX toDouble $ mapSizeY toDouble $ fragmentSize self
    box = mapX' toDouble $ mapY' toDouble box'
treeBox self@(Leaf Fragment { fragmentUserData = (_, box', _)}) = box' {
    Box.min = size', Box.max = size', Box.size = size', Box.nat = size
  } where
    size' = mapSizeX fromDouble $ mapSizeY fromDouble size
    size = mapSizeX (subtract $ hSpace box) $ mapSizeY (subtract $ vSpace box) $
        mapSizeX toDouble $ mapSizeY toDouble $ fragmentSize self
    box = mapX' toDouble $ mapY' toDouble box'

-- | Variant of `fragmentSize` asserting to the typesystem that both fields
-- of the resulting `Size` are of the same type.
fragmentSize' :: CastDouble x => FragmentTree (a, PaddedBox x x, c) -> Size x x
fragmentSize' = fragmentSize -- Work around for typesystem.
-- | Retrieve the position of a fragment.
fragmentPos :: (Double, Double) -> Fragment a -> (Double, Double)
fragmentPos (x, y) self = (x + hbScale (x_min r), y + hbScale (y_min r))
    where r = fragmentRect self

reconstructTree :: Eq x => ParagraphLayout x -> [FragmentTree x]
reconstructTree ParagraphLayout { paragraphFragments = frags } =
    reconstructTree' [frag {
            fragmentAncestorBoxes = reverse $ fragmentAncestorBoxes frag
        } | frag <- frags]
reconstructTree' :: Eq x => [Fragment x] -> [FragmentTree x]
reconstructTree' (self@Fragment { fragmentAncestorBoxes = [] }:frags) =
    Leaf self:reconstructTree' frags
reconstructTree' frags@(Fragment {
        fragmentAncestorBoxes = branch:_, fragmentLine = line
  }:_) =
    Branch branch (reconstructTree' [ child { fragmentAncestorBoxes = ancestors }
            | child@Fragment { fragmentAncestorBoxes = _:ancestors } <- childs])
        :reconstructTree' sibs
  where
    (childs, sibs) = span sameBranch frags
    -- Cluster ancestor branches, breaking them per-line.
    sameBranch Fragment {fragmentAncestorBoxes=branch':_, fragmentLine=line'} =
        branch == branch' && line == line'
    -- Leaves are always in their own branch.
    sameBranch Fragment { fragmentAncestorBoxes = [] } = False
reconstructTree' [] = []

positionTree :: (CastDouble m, CastDouble n) => (Double, Double) ->
        FragmentTree (a, PaddedBox m n, c) ->
        FragmentTree (a, PaddedBox m n, ((Double, Double), c))
positionTree (x, y) self@(Branch (AncestorBox (a, b, c) d e f g) childs) =
    Branch (AncestorBox (a, b, (pos, c)) d e f g) $
        map (positionTree pos) childs
  where
    pos = (x + hbScale (x_min rect), y + hbScale (y_min rect))
    rect = treeRect self
positionTree (x, y) self@(Leaf (Fragment (a, b, c) d _ f g h)) =
    Leaf (Fragment (a, b, (pos, c)) d [] f g h)
  where
    pos = (x + hbScale (x_min rect), y + hbScale (y_min rect))
    rect = treeRect self
treeInner :: FragmentTree (a, b, c) -> c
treeInner (Branch AncestorBox { boxUserData = (_, _, ret) } _) = ret
treeInner (Leaf Fragment { fragmentUserData = (_, _, ret) }) = ret