mlib-svg.lmt /size: 140 Kb    last modification: 2025-02-21 11:03
1if not modules then modules = { } end modules ['mlib-svg'] = {
2    version   = 1.001,
3    optimize  = true,
4    comment   = "companion to mlib-ctx.mkiv",
5    author    = "Hans Hagen, PRAGMA-ADE, Hasselt NL",
6    copyright = "PRAGMA ADE / ConTeXt Development Team",
7    license   = "see context related readme files",
8}
9
10-- text: fill white also
11
12-- todo: svg stripper
13-- todo: check clip: what if larger than bbox
14-- todo: when opacity is 1 don't flush it
15
16-- Just a few notes:
17--
18-- There is no real need to boost performance here .. we can always make a fast
19-- variant when really needed. I will also do some of the todo's when I run into
20-- proper fonts. I need to optimize this a bit but will do that once I'm satisfied
21-- with the outcome and don't need more hooks and plugs. At some point I will
22-- optimize the MetaPost part because now we probably have more image wrapping
23-- than needed.
24--
25-- As usual with these standards, things like a path can be very compact while the
26-- rest is very verbose which defeats the point. This is a first attempt. There will
27-- be a converter to MP as well as directly to PDF. This module was made for one of
28-- the dangerous curves talks at the 2019 CTX meeting. I will do the font when I
29-- need it (not that hard).
30--
31-- The fact that in the more recent versions of SVG the older text related elements
32-- are depricated and not even supposed to be supported, combined with the fact that
33-- the text element assumes css styling, demonstrates that there is not so much as a
34-- standard. It basically means that whatever technology dominates at some point
35-- (probably combined with some libraries that at that point exist) determine what
36-- is standard. Anyway, it probably also means that these formats are not that
37-- suitable for long term archival purposes. So don't take the next implementation
38-- too serious. So in the end we now have (1) attributes for properties (which is
39-- nice and clean and what attributes are for, (2) a style attribute that needs to
40-- be parsed, (3) classes that map to styles and (4) element related styles, plus a
41-- kind of inheritance (given the limited number of elements sticking to only <g> as
42-- wrapper would have made much sense. Anyway, we need to deal with it. With all
43-- these style things going on, one can wonder where it will end. Basically svg
44-- became just a html element that way and less clean too. The same is true for
45-- tspan, which means that text itself is nested xml.
46--
47-- We can do a direct conversion to PDF but then we also loose the abstraction which
48-- in the future will be used, and for fonts we need to spawn out to TeX anyway, so
49-- the little overhead of calling MetaPost is okay I guess. Also, we want to
50-- overload labels, share fonts with the main document, etc. and are not aiming at a
51-- general purpose SVG converter. For going to PDF one can just use InkScape.
52--
53-- Written with Anne Clark on speakers as distraction.
54--
55-- Todo when I run into an example (but ony when needed and reasonable):
56--
57--   var(color,color)
58--   --color<decimal>
59--   currentColor : when i run into an example
60--   a bit more shading
61--   clip = [ auto | rect(llx,lly,urx,ury) ] (in svg)
62--   xlink url ... whatever
63--   masks
64--   opacity per group (i need to add that to metafun first, inefficient pdf but
65--   maybe filldraw can help here)
66--
67-- Maybe in metafun:
68--
69--   penciled    n     -> withpen pencircle scaled n
70--   applied     (...) -> transformed bymatrix (...)
71--   withopacity n     -> withtransparency (1,n)
72
73-- When testing mbo files:
74--
75--   empty paths
76--   missing control points
77--   funny fontnames like abcdefverdana etc
78--   paths representing glyphs but also with style specs
79--   all kind of attributes
80--   very weird and inefficient shading
81
82-- One can run into pretty crazy images, like lines that are fills being clipped
83-- to some width. That's the danger of hiding yourself behind an interface I guess.
84--
85-- One would expect official examples to sort of follow the structure guideline,
86-- like putting gradient definitions in a "defs" element but forget about it ...
87-- structure seems not to be important (one can even wonder why "defs" is there at
88-- all). In the end all these systems (tex macro packages included) end up as a
89-- mess simply because conceptually wrong input gets accepted as normal. A side
90-- effect is that one starts to get a disliking. Anyway, at sime point I can just
91-- simplify some code because ugliness is part of the game.
92
93-- What a mess: opacity=0.8 and fill-opacity=1 on the same element ...
94
95-- the fact that everything glyph is gone makes it less useful because now one is
96-- dependent of some text renderer which then also removes some control because one
97-- has to fight and/or abuse features to get a specific shape ... the same is true
98-- for browsers ... it makes that svg is not really an output format any longer so
99-- less useful in the end (so for instance to get a specific glyph one needs to find
100-- a feature that provides it .. likely per glyph (om the other hand creepy shading
101-- and opacity has to be supported that can easier be done otherwise) .. and what
102-- about optimizeSpeed, optimizeLegibility, geometricPrecision ... it basically makes
103-- using labels impossible because no one knows how it will align .. so best convert
104-- text to curves!
105
106local rawget, rawset, type, tonumber, tostring, next, setmetatable = rawget, rawset, type, tonumber, tostring, next, setmetatable
107
108local P, S, R, C, Ct, Cs, Cc, Cp, Cg, Cf, Carg = lpeg.P, lpeg.S, lpeg.R, lpeg.C, lpeg.Ct, lpeg.Cs, lpeg.Cc, lpeg.Cp, lpeg.Cg, lpeg.Cf, lpeg.Carg
109
110local lpegmatch, lpegpatterns = lpeg.match, lpeg.patterns
111local sqrt, abs = math.sqrt, math.abs
112local concat, setmetatableindex, sortedhash = table.concat, table.setmetatableindex, table.sortedhash
113local gmatch, gsub, find, match = string.gmatch, string.gsub, string.find, string.match
114local formatters, fullstrip = string.formatters, string.fullstrip
115local utfsplit, utfbyte = utf.split, utf.byte
116
117local xmlconvert, xmlcollected, xmlcount, xmlfirst, xmlroot, xmlall = xml.convert, xml.collected, xml.count, xml.first, xml.root, xml.all
118local xmltext, xmltextonly = xml.text, xml.textonly
119local css = xml.css or { } -- testing
120
121local function xmlinheritattributes(c,pa)
122    if not c.special then
123        local at = c.at
124        local dt = c.dt
125        if at and dt then
126            if pa then
127                setmetatableindex(at,pa)
128            end
129            for i=1,#dt do
130                local dti = dt[i]
131                if type(dti) == "table" then
132                    xmlinheritattributes(dti,at)
133                end
134            end
135        end
136    end
137end
138
139xml.inheritattributes = xmlinheritattributes
140
141-- Maybe some day helpers will move to the metapost.svg namespace!
142
143metapost       = metapost or { }
144local metapost = metapost
145local context  = context
146
147local report       = logs.reporter("metapost","svg")
148
149local trace        = false  trackers.register("metapost.svg",        function(v) trace        = v end)
150local trace_text   = false  trackers.register("metapost.svg.text",   function(v) trace_text   = v end)
151local trace_path   = false  trackers.register("metapost.svg.path",   function(v) trace_path   = v end)
152local trace_result = false  trackers.register("metapost.svg.result", function(v) trace_result = v end)
153local trace_colors = false  trackers.register("metapost.svg.colors", function(v) trace_colors = v end)
154local trace_fonts  = false  trackers.register("metapost.svg.fonts",  function(v) trace_fonts  = v end)
155
156-- This is just an experiment. Todo: reset hash etc. Also implement an option handler.
157
158local s_draw_image_start <const> = "draw image ("
159local s_draw_image_stop  <const> = ") ;"
160
161local ignoredopacity = 1
162
163local svghash = false  do
164
165    local svglast = 0
166    local svglist = false
167
168    local function checkhash(t,k)
169        local n = svglast + 1
170        svglast = n
171        svglist[n] = k
172        t[k] = n
173        return n
174    end
175
176    function metapost.startsvghashing()
177        svglast = 0
178        svglist = { }
179        svghash = setmetatableindex(checkhash)
180    end
181
182    function metapost.stopsvghashing()
183        svglast = 0
184        svglist = false
185        svghash = false
186    end
187
188    interfaces.implement {
189        name      = "svghashed",
190        arguments = "integer",
191        actions   = function(n)
192            local t = svglist and svglist[n]
193            if t then
194                context(t)
195            end
196        end
197    }
198
199end
200
201-- We have quite some closures because otherwise we run into the local variable
202-- limitations. It doesn't always look pretty now, sorry. I'll clean up this mess
203-- some day (the usual nth iteration of code).
204--
205-- Most of the conversion is rather trivial code till I ran into a file with arcs. A
206-- bit of searching lead to the a2c javascript function but it has some puzzling
207-- thingies (like sin and cos definitions that look like leftovers and possible
208-- division by zero). Anyway, we can if needed optimize it a bit more. Here does it
209-- come from:
210
211-- http://www.w3.org/TR/SVG11/implnote.html#ArcImplementationNotes
212-- https://github.com/adobe-webplatform/Snap.svg/blob/b242f49e6798ac297a3dad0dfb03c0893e394464/src/path.js
213
214local a2c  do
215
216    local pi, sin, cos, tan, asin, abs = math.pi, math.sin, math.cos, math.tan, math.asin, math.abs
217
218    local d120 = (pi * 120) / 180
219    local pi2  = 2 * pi
220
221    a2c = function(x1, y1, rx, ry, angle, large, sweep, x2, y2, f1, f2, cx, cy)
222
223        if (rx == 0 or ry == 0) or (x1 == x2 and y1 == y2) then
224            return { x1, y1, x2, y2, x2, y2 }
225        end
226
227        local recursive = f1
228        local rad       = pi / 180 * angle
229        local res       = nil
230        local cosrad    = cos(-rad) -- local cosrad = cosd(angle)
231        local sinrad    = sin(-rad) -- local sinrad = sind(angle)
232
233        if not recursive then
234
235            x1, y1 = x1 * cosrad - y1 * sinrad, x1 * sinrad + y1 * cosrad
236            x2, y2 = x2 * cosrad - y2 * sinrad, x2 * sinrad + y2 * cosrad
237
238            local x  = (x1 - x2) / 2
239            local y  = (y1 - y2) / 2
240            local xx = x * x
241            local yy = y * y
242            local h  = xx / (rx * rx) + yy / (ry * ry)
243
244            if h > 1 then
245                h  = sqrt(h)
246                rx = h * rx
247                ry = h * ry
248            end
249
250            local rx2   = rx * rx
251            local ry2   = ry * ry
252            local ry2xx = ry2 * xx
253            local rx2yy = rx2 * yy
254            local total = rx2yy + ry2xx -- otherwise overflow
255
256            local k     = total == 0 and 0 or sqrt(abs((rx2 * ry2 - rx2yy - ry2xx) / total))
257
258            if large == sweep then
259                k = -k
260            end
261
262            cx = k *  rx * y / ry + (x1 + x2) / 2
263            cy = k * -ry * x / rx + (y1 + y2) / 2
264
265            f1 = (y1 - cy) / ry -- otherwise crash on a tiny eps
266            f2 = (y2 - cy) / ry -- otherwise crash on a tiny eps
267
268            f1 = asin((f1 < -1.0 and -1.0) or (f1 > 1.0 and 1.0) or f1)
269            f2 = asin((f2 < -1.0 and -1.0) or (f2 > 1.0 and 1.0) or f2)
270
271            if x1 < cx then f1 = pi  - f1 end
272            if x2 < cx then f2 = pi  - f2 end
273
274            if f1 < 0  then f1 = pi2 + f1 end
275            if f2 < 0  then f2 = pi2 + f2 end
276
277            if sweep ~= 0 and f1 > f2 then f1 = f1 - pi2 end
278            if sweep == 0 and f2 > f1 then f2 = f2 - pi2 end
279
280        end
281
282        if abs(f2 - f1) > d120 then
283            local f2old = f2
284            local x2old = x2
285            local y2old = y2
286            f2 = f1 + d120 * ((sweep ~= 0 and f2 > f1) and 1 or -1)
287            x2 = cx + rx * cos(f2)
288            y2 = cy + ry * sin(f2)
289            res = a2c(x2, y2, rx, ry, angle, 0, sweep, x2old, y2old, f2, f2old, cx, cy)
290        end
291
292        local c1 = cos(f1)
293        local s1 = sin(f1)
294        local c2 = cos(f2)
295        local s2 = sin(f2)
296
297        local t  = tan((f2 - f1) / 4)
298        local hx = 4 * rx * t / 3
299        local hy = 4 * ry * t / 3
300
301        local r = { x1 - hx * s1, y1 + hy * c1, x2 + hx * s2, y2 - hy * c2, x2, y2, unpack(res or { }) }
302
303        if not recursive then -- we can also check for sin/cos being 0/1
304            cosrad = cos(rad)
305            sinrad = sin(rad)
306         -- cosrad = cosd(angle)
307         -- sinrad = sind(angle)
308            for i0=1,#r,2 do
309                local i1 = i0 + 1
310                local x  = r[i0]
311                local y  = r[i1]
312                r[i0] = x * cosrad - y * sinrad
313                r[i1] = x * sinrad + y * cosrad
314            end
315        end
316
317        return r
318    end
319
320end
321
322-- We share some patterns.
323
324local p_digit    = lpegpatterns.digit
325local p_hexdigit = lpegpatterns.hexdigit
326local p_space    = lpegpatterns.whitespace
327
328local factors = {
329    ["pt"] =  1.25,
330    ["mm"] =  3.543307,
331    ["cm"] = 35.43307,
332    ["px"] =  1,
333    ["pc"] = 15,
334    ["in"] = 90,
335    ["em"] = 12 * 1.25,
336    ["ex"] =  8 * 1.25,
337    ["%"]  =  0.1,
338    ["bp"] =  1,
339}
340
341metapost.svgfactors = factors
342
343local percentage_r = 1/100
344local percentage_x = percentage_r
345local percentage_y = percentage_r
346
347local asnumber, asnumber_r, asnumber_x, asnumber_y, asnumber_vx, asnumber_vy
348local asnumber_vx_t, asnumber_vy_t
349local p_number, p_separator, p_optseparator, p_numbers, p_fournumbers, p_path
350local p_number_n, p_number_x, p_number_vx, p_number_y, p_number_vy, p_number_r
351
352do
353
354    -- incredible: we can find .123.456 => 0.123 0.456 ...
355
356    local p_command_x  = C(S("Hh"))
357    local p_command_y  = C(S("Vv"))
358    local p_command_xy = C(S("CcLlMmQqSsTt"))
359    local p_command_a  = C(S("Aa"))
360    local p_command    = C(S("Zz"))
361
362    p_optseparator = S("\t\n\r ,")^0
363    p_separator    = S("\t\n\r ,")^1
364    p_number       = (S("+-")^0 * (p_digit^0 * P(".") * p_digit^1 + p_digit^1 * P(".") + p_digit^1))
365                   * (P("e") * S("+-")^0 * p_digit^1)^-1
366
367    local function convert   (n)   n =   tonumber(n)                                                                           return n     end
368    local function convert_p (n,u) n =   tonumber(n) if u == true then return n / 100                                     else return n end end
369    local function convert_r (n,u) n =   tonumber(n) if u == true then return percentage_r * n elseif u then return u * n else return n end end
370    local function convert_x (n,u) n =   tonumber(n) if u == true then return percentage_x * n elseif u then return u * n else return n end end
371    local function convert_y (n,u) n =   tonumber(n) if u == true then return percentage_y * n elseif u then return u * n else return n end end
372    local function convert_vx(n,u) n =   tonumber(n) if u == true then return percentage_x * n elseif u then return u * n else return n end end
373    local function convert_vy(n,u) n = - tonumber(n) if u == true then return percentage_y * n elseif u then return u * n else return n end end
374
375    local p_unit      = (P("p") * S("txc") + P("e") * S("xm") + S("mc") * P("m") + P("in")) / factors
376    local p_percent   = P("%") * Cc(true)
377
378    local c_number_n  = C(p_number)
379    local c_number_u  = C(p_number) * (p_percent + p_unit)^-1
380
381    p_number_n  = c_number_n / convert
382    p_number_u  = c_number_u / convert
383    p_number_x  = c_number_u / convert_x
384    p_number_vx = c_number_u / convert_vx
385    p_number_y  = c_number_u / convert_y
386    p_number_vy = c_number_u / convert_vy
387    p_number_r  = c_number_u / convert_r
388    p_number_p  = c_number_u / convert_p
389
390    asnumber    = function(s) return s and lpegmatch(p_number,   s) or 0 end
391    asnumber_r  = function(s) return s and lpegmatch(p_number_r, s) or 0 end
392    asnumber_p  = function(s) return s and lpegmatch(p_number_p, s) or 0 end
393    asnumber_x  = function(s) return s and lpegmatch(p_number_x, s) or 0 end
394    asnumber_y  = function(s) return s and lpegmatch(p_number_y, s) or 0 end
395    asnumber_vx = function(s) return s and lpegmatch(p_number_vx,s) or 0 end
396    asnumber_vy = function(s) return s and lpegmatch(p_number_vy,s) or 0 end
397
398    local p_number_vx_t = Ct { (p_number_vx + p_separator)^1 }
399    local p_number_vy_t = Ct { (p_number_vy + p_separator)^1 }
400
401    local zerotable = { 0 }
402
403    asnumber_vx_t = function(s) return s and lpegmatch(p_number_vx_t,s) or zerotable end
404    asnumber_vy_t = function(s) return s and lpegmatch(p_number_vy_t,s) or zerotable end
405
406--     local p_numbersep   = p_number_n + p_separator
407    local p_numbersep   = p_number_u + p_separator
408          p_numbers     = p_optseparator * P("(") * p_numbersep^0 * p_optseparator * P(")")
409          p_fournumbers = p_numbersep^4
410          p_path        = Ct ( (
411          p_command_xy * (p_optseparator * p_number_vx *
412                          p_optseparator * p_number_vy )^1
413        + p_command_x  * (p_optseparator * p_number_vx )^1
414        + p_command_y  * (p_optseparator * p_number_vy )^1
415        + p_command_a  * (p_optseparator * p_number_vx *
416                          p_optseparator * p_number_vy *
417                          p_optseparator * p_number_r  *
418                          p_optseparator * p_number_n  * -- flags
419                          p_optseparator * p_number_n  * -- flags
420                          p_optseparator * p_number_vx *
421                          p_optseparator * p_number_vy )^1
422        + p_command
423        + p_separator
424    )^1 )
425
426
427end
428
429-- We can actually use the svg color definitions from the tex end but maybe a user
430-- doesn't want those replace the normal definitions.
431--
432-- local hexhash  = setmetatableindex(function(t,k) local v = lpegmatch(p_hexcolor, k) t[k] = v return v end)  -- per file
433-- local hexhash3 = setmetatableindex(function(t,k) local v = lpegmatch(p_hexcolor3,k) t[k] = v return v end)  -- per file
434--
435-- local function hexcolor (c) return hexhash [c] end -- directly do hexhash [c]
436-- local function hexcolor3(c) return hexhash3[c] end -- directly do hexhash3[c]
437
438local colormap  = false
439
440local function prepared(t)
441    if type(t) == "table" then
442        local mapping = t.mapping or { }
443        local mapper  = t.mapper
444        local colormap = setmetatableindex(mapping)
445        if mapper then
446            setmetatableindex(colormap,function(t,k)
447                local v = mapper(k)
448                t[k] = v or k
449                return v
450            end)
451        end
452        return colormap
453    else
454        return false
455    end
456end
457
458local colormaps = setmetatableindex(function(t,k)
459    local v = false
460    if type(k) == "string" then
461        v = prepared(table.load(k)) -- todo: same path as svg file
462    elseif type(k) == "table" then
463        v = prepared(k)
464        k = k.name or k
465    end
466    t[k] = v
467    return v
468end)
469
470function metapost.svgcolorremapper(colormap)
471    return colormaps[colormap]
472end
473
474-- todo: cache colors per image / remapper
475
476local colorcomponents, withcolor, thecolor, usedcolors  do
477
478    local svgcolors = {
479        aliceblue       = 0xF0F8FF, antiquewhite      = 0xFAEBD7, aqua                  = 0x00FFFF, aquamarine       = 0x7FFFD4,
480        azure           = 0xF0FFFF, beige             = 0xF5F5DC, bisque                = 0xFFE4C4, black            = 0x000000,
481        blanchedalmond  = 0xFFEBCD, blue              = 0x0000FF, blueviolet            = 0x8A2BE2, brown            = 0xA52A2A,
482        burlywood       = 0xDEB887, cadetblue         = 0x5F9EA0, hartreuse             = 0x7FFF00, chocolate        = 0xD2691E,
483        coral           = 0xFF7F50, cornflowerblue    = 0x6495ED, cornsilk              = 0xFFF8DC, crimson          = 0xDC143C,
484        cyan            = 0x00FFFF, darkblue          = 0x00008B, darkcyan              = 0x008B8B, darkgoldenrod    = 0xB8860B,
485        darkgray        = 0xA9A9A9, darkgreen         = 0x006400, darkgrey              = 0xA9A9A9, darkkhaki        = 0xBDB76B,
486        darkmagenta     = 0x8B008B, darkolivegreen    = 0x556B2F, darkorange            = 0xFF8C00, darkorchid       = 0x9932CC,
487        darkred         = 0x8B0000, darksalmon        = 0xE9967A, darkseagreen          = 0x8FBC8F, darkslateblue    = 0x483D8B,
488        darkslategray   = 0x2F4F4F, darkslategrey     = 0x2F4F4F, darkturquoise         = 0x00CED1, darkviolet       = 0x9400D3,
489        deeppink        = 0xFF1493, deepskyblue       = 0x00BFFF, dimgray               = 0x696969, dimgrey          = 0x696969,
490        dodgerblue      = 0x1E90FF, firebrick         = 0xB22222, floralwhite           = 0xFFFAF0, forestgreen      = 0x228B22,
491        fuchsia         = 0xFF00FF, gainsboro         = 0xDCDCDC, ghostwhite            = 0xF8F8FF, gold             = 0xFFD700,
492        goldenrod       = 0xDAA520, gray              = 0x808080, green                 = 0x008000, greenyellow      = 0xADFF2F,
493        grey            = 0x808080, honeydew          = 0xF0FFF0, hotpink               = 0xFF69B4, indianred        = 0xCD5C5C,
494        indigo          = 0x4B0082, ivory             = 0xFFFFF0, khaki                 = 0xF0E68C, lavender         = 0xE6E6FA,
495        lavenderblush   = 0xFFF0F5, lawngreen         = 0x7CFC00, lemonchiffon          = 0xFFFACD, lightblue        = 0xADD8E6,
496        lightcoral      = 0xF08080, lightcyan         = 0xE0FFFF, lightgoldenrodyellow  = 0xFAFAD2, lightgray        = 0xD3D3D3,
497        lightgreen      = 0x90EE90, lightgrey         = 0xD3D3D3, lightpink             = 0xFFB6C1, lightsalmon      = 0xFFA07A,
498        lightseagreen   = 0x20B2AA, lightskyblue      = 0x87CEFA, lightslategray        = 0x778899, lightslategrey   = 0x778899,
499        lightsteelblue  = 0xB0C4DE, lightyellow       = 0xFFFFE0, lime                  = 0x00FF00, limegreen        = 0x32CD32,
500        linen           = 0xFAF0E6, magenta           = 0xFF00FF, maroon                = 0x800000, mediumaquamarine = 0x66CDAA,
501        mediumblue      = 0x0000CD, mediumorchid      = 0xBA55D3, mediumpurple          = 0x9370DB, mediumseagreen   = 0x3CB371,
502        mediumslateblue = 0x7B68EE, mediumspringgreen = 0x00FA9A, mediumturquoise       = 0x48D1CC, mediumvioletred  = 0xC71585,
503        midnightblue    = 0x191970, mintcream         = 0xF5FFFA, mistyrose             = 0xFFE4E1, moccasin         = 0xFFE4B5,
504        navajowhite     = 0xFFDEAD, navy              = 0x000080, oldlace               = 0xFDF5E6, olive            = 0x808000,
505        olivedrab       = 0x6B8E23, orange            = 0xFFA500, orangered             = 0xFF4500, orchid           = 0xDA70D6,
506        palegoldenrod   = 0xEEE8AA, palegreen         = 0x98FB98, paleturquoise         = 0xAFEEEE, palevioletred    = 0xDB7093,
507        papayawhip      = 0xFFEFD5, peachpuff         = 0xFFDAB9, peru                  = 0xCD853F, pink             = 0xFFC0CB,
508        plum            = 0xDDA0DD, powderblue        = 0xB0E0E6, purple                = 0x800080, red              = 0xFF0000,
509        rosybrown       = 0xBC8F8F, royalblue         = 0x4169E1, saddlebrown           = 0x8B4513, salmon           = 0xFA8072,
510        sandybrown      = 0xF4A460, seagreen          = 0x2E8B57, seashell              = 0xFFF5EE, sienna           = 0xA0522D,
511        silver          = 0xC0C0C0, skyblue           = 0x87CEEB, slateblue             = 0x6A5ACD, slategray        = 0x708090,
512        slategrey       = 0x708090, snow              = 0xFFFAFA, springgreen           = 0x00FF7F, steelblue        = 0x4682B4,
513        tan             = 0xD2B48C, teal              = 0x008080, thistle               = 0xD8BFD8, tomato           = 0xFF6347,
514        turquoise       = 0x40E0D0, violet            = 0xEE82EE, wheat                 = 0xF5DEB3, white            = 0xFFFFFF,
515        whitesmoke      = 0xF5F5F5, yellow            = 0xFFFF00, yellowgreen           = 0x9ACD32,
516    }
517
518    local f_rgb      = formatters['    withcolor svgcolor(%.3N,%.3N,%.3N)']
519    local f_cmyk     = formatters['    withcolor svgcmyk(%.3N,%.3N,%.3N,%.3N)']
520    local f_gray     = formatters['    withcolor svggray(%.3N)']
521    local f_rgba     = formatters['    withcolor svgcolor(%.3N,%.3N,%.3N) withopacity %.3N']
522    local f_graya    = formatters['    withcolor svggray(%.3N) withopacity %.3N']
523    local f_name     = formatters['    withcolor "%s"']
524    local f_svgrgb   = formatters['svgcolor(%.3N,%.3N,%.3N)']
525    local f_svgcmyk  = formatters['svgcmyk(%.3N,%.3N,%.3N,%.3N)']
526    local f_svggray  = formatters['svggray(%.3N)']
527    local f_svgname  = formatters['"%s"']
528
529    local triplets = setmetatableindex(function(t,k)
530        -- we delay building all these strings
531        local v = svgcolors[k]
532        if v then
533            v = { ((v>>16)&0xFF)/0xFF, ((v>>8)&0xFF)/0xFF, ((v>>0)&0xFF)/0xFF }
534        else
535            v = false
536        end
537        t[k] = v
538        return v
539    end)
540
541    local p_fraction  = C(p_number) * C("%")^-1  / function(a,b) return tonumber(a) / (b and 100 or 255) end
542    local p_angle     = C(p_number) * P("deg")^0 / function(a)   return tonumber(a) end
543    local p_percent   = C(p_number) * P("%")     / function(a)   return tonumber(a) / 100 end
544    local p_absolute  = C(p_number)              / tonumber
545
546    local p_left      = P("(")
547    local p_right     = P(")")
548    local p_a         = P("a")^-1
549    local p_r_a_color = p_left
550                      * (p_fraction * p_separator^-1)^-3
551                      * p_absolute^0
552                      * p_right
553    local p_c_k_color = p_left
554                      * (p_absolute + p_separator^-1)^-4
555                      * p_right
556    local p_h_a_color = p_left
557                      * p_angle
558                      * p_separator   * p_percent
559                      * p_separator   * p_percent
560                      * p_separator^0 * p_absolute^0
561                      * p_right
562
563    local colors      = attributes.colors
564    local colorvalues = colors.values
565    local colorindex  = attributes.list[attributes.private('color')]
566    local hsvtorgb    = colors.hsvtorgb
567    local hwbtorgb    = colors.hwbtorgb
568    local forcedmodel = colors.forcedmodel
569
570    local function to_rgb(r,g,b)
571        return "rgb",
572            (r == "00" and 0) or (r == "ff" and 1) or (r == "FF" and 1) or (tonumber(r,16)/255),
573            (g == "00" and 0) or (g == "ff" and 1) or (g == "FF" and 1) or (tonumber(g,16)/255),
574            (b == "00" and 0) or (b == "ff" and 1) or (b == "FF" and 1) or (tonumber(b,16)/255)
575    end
576
577    local function to_gray(s)
578        return "gray",
579            (s == "00" and 0) or (s == "ff" and 1) or (s == "FF" and 1) or (tonumber(s,16)/255)
580    end
581
582    local p_splitcolor =
583        P("#") * C(p_hexdigit)^1 / function(a,b,c,d,e,f)
584            if not a then
585                return "gray", 0
586            elseif not b then
587                return to_gray(a..a)
588            elseif not c then
589                return to_gray(a..b)
590            elseif not d then
591                return to_rgb(a..a,b..b,c..c)
592            elseif e and f then
593                return to_rgb(a..b,c..d,e..f)
594            else
595                return "gray", 0
596            end
597        end
598      + P("rgb") * p_a
599      * p_r_a_color / function(r,g,b,a)
600            return "rgb", r or 0, g or 0, b or 0, a or false
601        end
602      + P("cmyk")
603      * p_c_k_color / function(c,m,y,k)
604            return "cmyk", c or 0, m or 0, y or 0, k or 0
605        end
606      + P("hsl") * p_a
607      * p_h_a_color / function(h,s,l,a)
608            local r, g, b = hsvtorgb(h,s,l,a)
609            return "rgb", r or 0, g or 0, b or 0, a or false
610        end
611      + P("hwb") * p_a
612      * p_h_a_color / function(h,w,b,a)
613            local r, g, b = hwbtorgb(h,w,b)
614            return "rgb", r or 0, g or 0, b or 0, a or false
615        end
616
617    function metapost.svgsplitcolor(color)
618        if type(color) == "string" then
619            local what, s1, s2, s3, s4 = lpegmatch(p_splitcolor,color)
620            if not what then
621                local t = triplets[color]
622                if t then
623                    what, s1, s2, s3 = "rgb", t[1], t[2], t[3]
624                end
625            end
626            return what, s1, s2, s3, s4
627        else
628            return "gray", 0, false
629        end
630    end
631
632    local function registeredcolor(name)
633        local color = colorindex[name]
634        if color then
635            local v = colorvalues[color]
636            local t = forcedmodel(v[1])
637            if t == 2 then
638                return "gray", v[2]
639            elseif t == 3 then
640                return "rgb", v[3], v[4], v[5]
641            elseif t == 4 then
642                return "cmyk", v[6], v[7], v[8], v[9]
643            else
644                --
645            end
646        end
647    end
648
649    -- we can have a fast check for #000000
650
651    local function validcolor(color)
652        if usedcolors then
653            usedcolors[color] = usedcolors[color] + 1
654        end
655        if colormap then
656            local c = colormap[color]
657            local t = type(c)
658            if t == "table" then
659                local what = t[1]
660                if what == "rgb" then
661                    return
662                        what,
663                        tonumber(t[2]) or 0,
664                        tonumber(t[3]) or 0,
665                        tonumber(t[4]) or 0,
666                        tonumber(t[5]) or false
667                elseif what == "cmyk" then
668                    return
669                        what,
670                        tonumber(t[2]) or 0,
671                        tonumber(t[3]) or 0,
672                        tonumber(t[4]) or 0,
673                        tonumber(t[5]) or 0
674                elseif what == "gray" then
675                    return
676                        what,
677                        tonumber(t[2]) or 0,
678                        tonumber(t[3]) or false
679                end
680            elseif t == "string" then
681                color = c
682            end
683        end
684        if color == "#000000" then
685            return "rgb", 0, 0, 0
686        elseif color == "#ffffff" then
687            return "rgb", 1, 1, 1
688        else
689            local what, s1, s2, s3, s4 = registeredcolor(color)
690            if not what then
691                what, s1, s2, s3, s4 = lpegmatch(p_splitcolor,color)
692                -- we could cache
693                if not what then
694                    local t = triplets[color]
695                    if t then
696                        s1, s2, s3 = t[1], t[2], t[3]
697                        what = "rgb"
698                    end
699                end
700            end
701            return what, s1, s2, s3, s4
702        end
703    end
704
705    colorcomponents = function(color)
706        local what, s1, s2, s3, s4 = validcolor(color)
707        return s1, s2, s3, s4 -- so 4 means cmyk
708    end
709
710    withcolor = function(color)
711        local what, s1, s2, s3, s4 = validcolor(color)
712        if what == "rgb" then
713            if s4 then
714                if s1 == s2 and s1 == s3 then
715                    return f_graya(s1,s4)
716                else
717                    return f_rgba(s1,s2,s3,s4)
718                end
719            else
720                if s1 == s2 and s1 == s3 then
721                    return f_gray(s1)
722                else
723                    return f_rgb(s1,s2,s3)
724                end
725            end
726        elseif what == "cmyk" then
727            return f_cmyk(s1,s2,s3,s4)
728        elseif what == "gray" then
729            if s2 then
730                return f_graya(s1,s2)
731            else
732                return f_gray(s1)
733            end
734        end
735        return f_name(color)
736    end
737
738    thecolor = function(color)
739        local what, s1, s2, s3, s4 = validcolor(color)
740        if what == "rgb" then
741            if s4 then
742                if s1 == s2 and s1 == s3 then
743                    return f_svggraya(s1,s4)
744                else
745                    return f_svgrgba(s1,s2,s3,s4)
746                end
747            else
748                if s1 == s2 and s1 == s3 then
749                    return f_svggray(s1)
750                else
751                    return f_svgrgb(s1,s2,s3)
752                end
753            end
754        elseif what == "cmyk" then
755            return f_cmyk(s1,s2,s3,s4)
756        elseif what == "gray" then
757            if s2 then
758                return f_svggraya(s1,s2)
759            else
760                return f_svggray(s1)
761            end
762        end
763        return f_svgname(color)
764    end
765
766end
767
768-- actually we can loop faster because we can go to the last one
769
770local grabpath, grablist  do
771
772    local f_moveto    = formatters['(%N,%N)']
773    local f_curveto_z = formatters['controls(%N,%N)and(%N,%N)..(%N,%N)']
774    local f_curveto_n = formatters['..controls(%N,%N)and(%N,%N)..(%N,%N)']
775    local f_lineto_z  = formatters['(%N,%N)']
776    local f_lineto_n  = formatters['--(%N,%N)']
777
778    local m = { __index = function() return 0 end }
779
780 -- local t      = { }    -- no real saving here if we share
781 -- local n      = 0
782
783    grabpath = function(str)
784        local p   = lpegmatch(p_path,str) or { }
785        local np  = #p
786        local all = { entries = np, closed = false, curve = false }
787        if np == 0 then
788            return all
789        end
790        setmetatable(p,m)
791        local t      = { }    -- no real saving here if we share
792        local n      = 0
793        local i      = 0
794        local last   = "M"
795        local prev   = last
796        local kind   = "L"
797        local x, y   = 0, 0
798        local x1, y1 = 0, 0
799        local x2, y2 = 0, 0
800        local rx, ry = 0, 0
801        local ar, al = 0, 0
802        local as, ac = 0, nil
803        local mx, my = 0, 0
804        while i < np do
805            i = i + 1
806            local pi = p[i]
807            if type(pi) ~= "number" then
808                last = pi
809                i    = i + 1
810                pi   = p[i]
811            end
812            -- most often
813            if last == "c" then
814                            x1 = x + pi
815                i = i + 1 ; y1 = y + p[i]
816                i = i + 1 ; x2 = x + p[i]
817                i = i + 1 ; y2 = y + p[i]
818                i = i + 1 ; x  = x + p[i]
819                i = i + 1 ; y  = y + p[i]
820                goto curveto
821            elseif last == "l" then
822                            x = x + pi
823                i = i + 1 ; y = y + p[i]
824                goto lineto
825            elseif last == "h" then
826                x = x + pi
827                goto lineto
828            elseif last == "v" then
829                y = y + pi
830                goto lineto
831            elseif last == "a" then
832                            x1 =     x
833                            y1 =     y
834                            rx =     pi
835                i = i + 1 ; ry =     p[i]
836                i = i + 1 ; ar =     p[i]
837                i = i + 1 ; al =     p[i]
838                i = i + 1 ; as =     p[i]
839                i = i + 1 ; x  = x + p[i]
840                i = i + 1 ; y  = y + p[i]
841                goto arc
842            elseif last == "s" then
843                if prev == "C" then
844                    x1 = 2 * x - x2
845                    y1 = 2 * y - y2
846                else
847                    x1 = x
848                    y1 = y
849                end
850                            x2 = x + pi
851                i = i + 1 ; y2 = y + p[i]
852                i = i + 1 ; x  = x + p[i]
853                i = i + 1 ; y  = y + p[i]
854                goto curveto
855            elseif last == "m" then
856                            x = x + pi
857                i = i + 1 ; y = y + p[i]
858                goto moveto
859            elseif last == "z" then
860                goto close
861            -- less frequent
862            elseif last == "C" then
863                            x1 = pi
864                i = i + 1 ; y1 = p[i]
865                i = i + 1 ; x2 = p[i]
866                i = i + 1 ; y2 = p[i]
867                i = i + 1 ; x  = p[i]
868                i = i + 1 ; y  = p[i]
869                goto curveto
870            elseif last == "L" then
871                            x = pi
872                i = i + 1 ; y = p[i]
873                goto lineto
874            elseif last == "H" then
875                x = pi
876                goto lineto
877            elseif last == "V" then
878                y = pi
879                goto lineto
880            elseif last == "A" then
881                            x1 = x
882                            y1 = y
883                            rx = pi
884                i = i + 1 ; ry = p[i]
885                i = i + 1 ; ar = p[i]
886                i = i + 1 ; al = p[i]
887                i = i + 1 ; as = p[i]
888                i = i + 1 ; x  = p[i]
889                i = i + 1 ; y  = p[i]
890                goto arc
891            elseif last == "S" then
892                if prev == "C" then
893                    x1 = 2 * x - x2
894                    y1 = 2 * y - y2
895                else
896                    x1 = x
897                    y1 = y
898                end
899                            x2 = pi
900                i = i + 1 ; y2 = p[i]
901                i = i + 1 ; x  = p[i]
902                i = i + 1 ; y  = p[i]
903                goto curveto
904            elseif last == "M" then
905                            x = pi ;
906                i = i + 1 ; y = p[i]
907                goto moveto
908            elseif last == "Z" then
909                goto close
910            -- very seldom
911            elseif last == "q" then
912                            x1 = x + pi
913                i = i + 1 ; y1 = y + p[i]
914                i = i + 1 ; x2 = x + p[i]
915                i = i + 1 ; y2 = y + p[i]
916                goto quadratic
917            elseif last == "t" then
918                if prev == "C" then
919                    x1 = 2 * x - x1
920                    y1 = 2 * y - y1
921                else
922                    x1 = x
923                    y1 = y
924                end
925                            x2 = x + pi
926                i = i + 1 ; y2 = y + p[i]
927                goto quadratic
928            elseif last == "Q" then
929                            x1 = pi
930                i = i + 1 ; y1 = p[i]
931                i = i + 1 ; x2 = p[i]
932                i = i + 1 ; y2 = p[i]
933                goto quadratic
934            elseif last == "T" then
935                if prev == "C" then
936                    x1 = 2 * x - x1
937                    y1 = 2 * y - y1
938                else
939                    x1 = x
940                    y1 = y
941                end
942                            x2 = pi
943                i = i + 1 ; y2 = p[i]
944                goto quadratic
945            else
946                goto continue
947            end
948            ::moveto::
949                if n > 0 then
950                    n = n + 1 ; t[n] = "&&"
951                end
952                n = n + 1 ; t[n] = f_moveto(x,y)
953                last = last == "M" and "L" or "l"
954                prev = "M"
955                mx = x
956                my = y
957                goto continue
958            ::lineto::
959                n = n + 1 ; t[n] = (n > 0 and f_lineto_n or f_lineto_z)(x,y)
960                prev = "L"
961                goto continue
962            ::curveto::
963                n = n + 1 ; t[n] = (n > 0 and f_curveto_n or f_curveto_z)(x1,y1,x2,y2,x,y)
964                prev = "C"
965                goto continue
966            ::arc::
967                ac = a2c(x1,y1,rx,ry,ar,al,as,x,y)
968                for i=1,#ac,6 do
969                    n = n + 1 ; t[n] = (n > 0 and f_curveto_n or f_curveto_z)(
970                        ac[i],ac[i+1],ac[i+2],ac[i+3],ac[i+4],ac[i+5]
971                    )
972                end
973                prev = "A"
974                goto continue
975            ::quadratic::
976                n = n + 1 ; t[n] = (n > 0 and f_curveto_n or f_curveto_z)(
977                    x  + 2/3 * (x1-x ), y  + 2/3 * (y1-y ),
978                    x2 + 2/3 * (x1-x2), y2 + 2/3 * (y1-y2),
979                    x2,                 y2
980                )
981                x = x2
982                y = y2
983                prev = "C"
984                goto continue
985            ::close::
986                if i == np then
987                    break
988                else
989                    i = i - 1
990                end
991                kind = prev
992                prev = "Z"
993                -- this is kind of undocumented: a close also moves back
994                x = mx
995                y = my
996            ::continue::
997        end
998        if n > 0 then
999            if prev == "Z" then
1000                all.closed = true
1001                n = n + 1 ; t[n] = "&&cycle"
1002            end
1003            all.path = concat(t,"",1,n)
1004        end
1005        all.curve = kind == "C" or kind == "A"
1006        return all, p
1007    end
1008
1009    -- this is a bit tricky as what are points for a mark ... the next can be simplified
1010    -- a lot
1011
1012    grablist = function(p)
1013        local np  = #p
1014        if np == 0 then
1015            return nil
1016        end
1017        local t      = { }
1018        local n      = 0
1019        local a      = 0
1020        local i      = 0
1021        local last   = "M"
1022        local prev   = last
1023        local kind   = "L"
1024        local x, y   = 0, 0
1025        local x1, y1 = 0, 0
1026        local x2, y2 = 0, 0
1027        local rx, ry = 0, 0
1028        local ar, al = 0, 0
1029        local as, ac = 0, nil
1030        local mx, my = 0, 0
1031        while i < np do
1032            i = i + 1
1033            local pi = p[i]
1034            if type(pi) ~= "number" then
1035                last = pi
1036                i    = i + 1
1037                pi   = p[i]
1038            end
1039            -- most often
1040            if last == "c" then
1041                            x1 = x + pi
1042                i = i + 1 ; y1 = y + p[i]
1043                i = i + 1 ; x2 = x + p[i]
1044                i = i + 1 ; y2 = y + p[i]
1045                i = i + 1 ; x  = x + p[i]
1046                i = i + 1 ; y  = y + p[i]
1047                goto curveto
1048            elseif last == "l" then
1049                            x = x + pi
1050                i = i + 1 ; y = y + p[i]
1051                goto lineto
1052            elseif last == "h" then
1053                x = x + pi
1054                goto lineto
1055            elseif last == "v" then
1056                y = y + pi
1057                goto lineto
1058            elseif last == "a" then
1059                            x1 =     x
1060                            y1 =     y
1061                            rx =     pi
1062                i = i + 1 ; ry =     p[i]
1063                i = i + 1 ; ar =     p[i]
1064                i = i + 1 ; al =     p[i]
1065                i = i + 1 ; as =     p[i]
1066                i = i + 1 ; x  = x + p[i]
1067                i = i + 1 ; y  = y + p[i]
1068                goto arc
1069            elseif last == "s" then
1070                if prev == "C" then
1071                    x1 = 2 * x - x2
1072                    y1 = 2 * y - y2
1073                else
1074                    x1 = x
1075                    y1 = y
1076                end
1077                            x2 = x + pi
1078                i = i + 1 ; y2 = y + p[i]
1079                i = i + 1 ; x  = x + p[i]
1080                i = i + 1 ; y  = y + p[i]
1081                goto curveto
1082            elseif last == "m" then
1083                            x = x + pi
1084                i = i + 1 ; y = y + p[i]
1085                goto moveto
1086            elseif last == "z" then
1087                goto close
1088            -- less frequent
1089            elseif last == "C" then
1090                            x1 = pi
1091                i = i + 1 ; y1 = p[i]
1092                i = i + 1 ; x2 = p[i]
1093                i = i + 1 ; y2 = p[i]
1094                i = i + 1 ; x  = p[i]
1095                i = i + 1 ; y  = p[i]
1096                goto curveto
1097            elseif last == "L" then
1098                            x = pi
1099                i = i + 1 ; y = p[i]
1100                goto lineto
1101            elseif last == "H" then
1102                x = pi
1103                goto lineto
1104            elseif last == "V" then
1105                y = pi
1106                goto lineto
1107            elseif last == "A" then
1108                            x1 = x
1109                            y1 = y
1110                            rx = pi
1111                i = i + 1 ; ry = p[i]
1112                i = i + 1 ; ar = p[i]
1113                i = i + 1 ; al = p[i]
1114                i = i + 1 ; as = p[i]
1115                i = i + 1 ; x  = p[i]
1116                i = i + 1 ; y  = p[i]
1117                goto arc
1118            elseif last == "S" then
1119                if prev == "C" then
1120                    x1 = 2 * x - x2
1121                    y1 = 2 * y - y2
1122                else
1123                    x1 = x
1124                    y1 = y
1125                end
1126                            x2 = pi
1127                i = i + 1 ; y2 = p[i]
1128                i = i + 1 ; x  = p[i]
1129                i = i + 1 ; y  = p[i]
1130                goto curveto
1131            elseif last == "M" then
1132                            x = pi ;
1133                i = i + 1 ; y = p[i]
1134                goto moveto
1135            elseif last == "Z" then
1136                goto close
1137            -- very seldom
1138            elseif last == "q" then
1139                            x1 = x + pi
1140                i = i + 1 ; y1 = y + p[i]
1141                i = i + 1 ; x2 = x + p[i]
1142                i = i + 1 ; y2 = y + p[i]
1143                goto quadratic
1144            elseif last == "t" then
1145                if prev == "C" then
1146                    x1 = 2 * x - x1
1147                    y1 = 2 * y - y1
1148                else
1149                    x1 = x
1150                    y1 = y
1151                end
1152                            x2 = x + pi
1153                i = i + 1 ; y2 = y + p[i]
1154                goto quadratic
1155            elseif last == "Q" then
1156                            x1 = pi
1157                i = i + 1 ; y1 = p[i]
1158                i = i + 1 ; x2 = p[i]
1159                i = i + 1 ; y2 = p[i]
1160                goto quadratic
1161            elseif last == "T" then
1162                if prev == "C" then
1163                    x1 = 2 * x - x1
1164                    y1 = 2 * y - y1
1165                else
1166                    x1 = x
1167                    y1 = y
1168                end
1169                            x2 = pi
1170                i = i + 1 ; y2 = p[i]
1171                goto quadratic
1172            else
1173                goto continue
1174            end
1175            ::moveto::
1176                n = n + 1 ; t[n] = x
1177                n = n + 1 ; t[n] = y
1178                last = last == "M" and "L" or "l"
1179                prev = "M"
1180                mx = x
1181                my = y
1182                goto continue
1183            ::lineto::
1184                n = n + 1 ; t[n] = x
1185                n = n + 1 ; t[n] = y
1186                prev = "L"
1187                goto continue
1188            ::curveto::
1189                n = n + 1 ; t[n] = x
1190                n = n + 1 ; t[n] = y
1191                prev = "C"
1192                goto continue
1193            ::arc::
1194                ac = a2c(x1,y1,rx,ry,ar,al,as,x,y)
1195                for i=1,#ac,6 do
1196                    n = n + 1 ; t[n] = ac[i+4]
1197                    n = n + 1 ; t[n] = ac[i+5]
1198                end
1199                prev = "A"
1200                goto continue
1201            ::quadratic::
1202                n = n + 1 ; t[n] = x2
1203                n = n + 1 ; t[n] = y2
1204                x = x2
1205                y = y2
1206                prev = "C"
1207                goto continue
1208            ::close::
1209                n = n + 1 ; t[n] = mx
1210                n = n + 1 ; t[n] = my
1211                if i == np then
1212                    break
1213                end
1214                kind = prev
1215                prev = "Z"
1216                x = mx
1217                y = my
1218            ::continue::
1219        end
1220        return t
1221    end
1222
1223end
1224
1225-- todo: viewbox helper
1226
1227local s_wrapped_start <const> = "draw image ("
1228local f_wrapped_stop          = formatters[") shifted (0,%N) scaled %N ;"]
1229
1230local handletransform, handleviewbox  do
1231
1232    local sind = math.sind
1233
1234    local f_rotatedaround           = formatters["rotatedaround((%N,%N),%N) "]
1235    local f_rotated                 = formatters["rotated(%N) "]
1236    local f_shifted                 = formatters["shifted(%N,%N) "]
1237    local f_slanted_x               = formatters["xslanted(%N) "]
1238    local f_slanted_y               = formatters["yslanted(%N) "]
1239    local f_scaled                  = formatters["scaled(%N) "]
1240    local f_xyscaled                = formatters["xyscaled(%N,%N) "]
1241    local f_matrix                  = formatters["transformed bymatrix(%N,%N,%N,%N,%N,%N) "]
1242    local s_transform_start <const> = "draw image ( "
1243    local f_transform_stop          = formatters[") %s ; "]
1244
1245    local transforms    = { }
1246    local noftransforms = 0
1247
1248    local function rotate(r,x,y)
1249        if r then
1250            noftransforms = noftransforms + 1
1251            if x then
1252                transforms[noftransforms] = f_rotatedaround(x,-(y or x),-r)
1253            else
1254                transforms[noftransforms] = f_rotated(-r)
1255            end
1256        end
1257    end
1258
1259    local function translate(x,y)
1260        if x == 0 then x = false end
1261        if y == 0 then y = false end
1262        if y then
1263            noftransforms = noftransforms + 1
1264            transforms[noftransforms] = f_shifted(x or 0,-y)
1265        elseif x then
1266            noftransforms = noftransforms + 1
1267            transforms[noftransforms] = f_shifted(x,0)
1268        end
1269    end
1270
1271    local function scale(x,y)
1272        if x == 1 then x = false end
1273        if y == 1 then y = false end
1274        if y then
1275            noftransforms = noftransforms + 1
1276            transforms[noftransforms] = f_xyscaled(x or 1,y)
1277        elseif x then
1278            noftransforms = noftransforms + 1
1279            transforms[noftransforms] = f_scaled(x)
1280        end
1281    end
1282
1283    local function skew(x,y)
1284     -- if x = 0 then x = false end
1285     -- if y = 0 then y = false end
1286        if x then
1287            noftransforms = noftransforms + 1
1288            transforms[noftransforms] = f_slanted_x(sind(-x))
1289        end
1290        if y then
1291            noftransforms = noftransforms + 1
1292            transforms[noftransforms] = f_slanted_y(sind(-y))
1293        end
1294    end
1295
1296    local function matrix(rx,sx,sy,ry,tx,ty)
1297        if not ty then
1298            ty = 0
1299        end
1300        if not tx then
1301            tx = 0
1302        end
1303        if not sx then
1304            sx = 0
1305        end
1306        if not sy then
1307            sy = 0
1308        end
1309        if not rx then
1310            rx = 1
1311        end
1312        if not ry then
1313            ry = 1
1314        end
1315        noftransforms = noftransforms + 1
1316     -- transforms[noftransforms] = f_matrix(rx, sx, sy, ry, tx, -ty)
1317        -- https://en.wikipedia.org/wiki/Rotation_matrix : we're counter clockwise
1318        transforms[noftransforms] = f_matrix(rx, -sy, -sx, ry, tx, -ty)
1319    end
1320
1321    local p_transform = (
1322            p_space^0 * (
1323            P("translate")  * (p_numbers / translate)      -- maybe xy
1324          + P("scale")      * (p_numbers / scale)
1325          + P("rotate")     * (p_numbers / rotate)
1326          + P("matrix")     * (p_numbers / matrix)
1327          + P("skew")       * (p_numbers / skew)
1328          + P("translateX") * (p_numbers / translate)
1329          + P("translateY") * (Cc(false) * p_numbers / translate)
1330          + P("scaleX")     * (p_numbers / translate)
1331          + P("scaleY")     * (Cc(false) * p_numbers / translate)
1332          + P("skewX")      * (p_numbers / skew)
1333          + P("skewY")      * (Cc(false) * p_numbers / skew)
1334        )
1335    )^1
1336
1337    -- indeed, we need to reverse the order ... not that pretty and counter intuitive too
1338
1339    local function combined()
1340        if noftransforms == 1 then
1341            return transforms[1]
1342        elseif noftransforms == 2 then
1343            return transforms[2] .. transforms[1]
1344        elseif noftransforms == 3 then
1345            return transforms[3] .. transforms[2] .. transforms[1]
1346        else
1347            -- the rare case (but anything can happen in svg and it gets worse)
1348            local m = noftransforms + 1
1349            for i=1,noftransforms//2 do
1350                local j = m - i
1351                transforms[i], transforms[j] = transforms[j], transforms[i]
1352            end
1353            return concat(transforms,"",1,noftransforms)
1354        end
1355    end
1356
1357    handletransform = function(at,unwrapped)
1358        local t = at.transform
1359        if t then
1360            noftransforms = 0
1361            lpegmatch(p_transform,t)
1362            if noftransforms > 0 then
1363                -- currentpicture
1364                return s_transform_start, f_transform_stop(combined()), t
1365            end
1366        end
1367    end
1368
1369    handletransformstring = function(s)
1370        if s then
1371            noftransforms = 0
1372            lpegmatch(p_transform,s)
1373            return noftransforms > 0 and combined()
1374        end
1375    end
1376
1377    handleviewbox = function(v)
1378        if v then
1379            local x, y, w, h = lpegmatch(p_fournumbers,v)
1380            if h then
1381                return x, y, w, h
1382            end
1383        end
1384    end
1385
1386end
1387
1388local dashed  do
1389
1390    -- actually commas are mandate but we're tolerant
1391
1392    local f_dashed_n = formatters[" dashed dashpattern (%s ) "]
1393    local f_dashed_y = formatters[" dashed dashpattern (%s ) shifted (%N,0) "]
1394
1395    local p_number   = p_optseparator/"" * p_number_r
1396    local p_on       = Cc(" on ")  * p_number
1397    local p_off      = Cc(" off ") * p_number
1398    local p_dashed   = Cs((p_on * p_off^-1)^1)
1399
1400    dashed = function(s,o)
1401        if not find(s,",") then
1402            -- a bit of a hack:
1403            s = s .. " " .. s
1404        end
1405        return (o and f_dashed_y or f_dashed_n)(lpegmatch(p_dashed,s),o)
1406    end
1407
1408end
1409
1410do
1411
1412    local handlers    = { }
1413    local process     = false
1414    local root        = false
1415    local result      = false
1416    local r           = false
1417    local definitions = false
1418    local classstyles = false
1419    local tagstyles   = false
1420
1421    local tags = {
1422        ["a"]                  = true,
1423     -- ["altgGlyph"]          = true,
1424     -- ["altgGlyphDef"]       = true,
1425     -- ["altgGlyphItem"]      = true,
1426     -- ["animate"]            = true,
1427     -- ["animateColor"]       = true,
1428     -- ["animateMotion"]      = true,
1429     -- ["animateTransform"]   = true,
1430        ["circle"]             = true,
1431        ["clipPath"]           = true,
1432     -- ["color-profile"]      = true,
1433     -- ["cursor"]             = true,
1434        ["defs"]               = true,
1435     -- ["desc"]               = true,
1436        ["ellipse"]            = true,
1437     -- ["filter"]             = true,
1438     -- ["font"]               = true,
1439     -- ["font-face"]          = true,
1440     -- ["font-face-format"]   = true,
1441     -- ["font-face-name"]     = true,
1442     -- ["font-face-src"]      = true,
1443     -- ["font-face-uri"]      = true,
1444     -- ["foreignObject"]      = true,
1445        ["g"]                  = true,
1446     -- ["glyph"]              = true,
1447     -- ["glyphRef"]           = true,
1448     -- ["hkern"]              = true,
1449        ["image"]              = true,
1450        ["line"]               = true,
1451        ["linearGradient"]     = true,
1452        ["marker"]             = true,
1453     -- ["mask"]               = true,
1454     -- ["metadata"]           = true,
1455     -- ["missing-glyph"]      = true,
1456     -- ["mpath"]              = true,
1457        ["path"]               = true,
1458        ["pattern"]            = true,
1459        ["polygon"]            = true,
1460        ["polyline"]           = true,
1461        ["radialGradient"]     = true,
1462        ["rect"]               = true,
1463     -- ["script"]             = true,
1464     -- ["set"]                = true,
1465        ["stop"]               = true,
1466        ["style"]              = true,
1467        ["svg"]                = true,
1468     -- ["switch"]             = true,
1469        ["symbol"]             = true,
1470        ["text"]               = true,
1471     -- ["textPath"]           = true,
1472     -- ["title"]              = true,
1473        ["tspan"]              = true,
1474        ["use"]                = true,
1475     -- ["view"]               = true,
1476     -- ["vkern"]              = true,
1477    }
1478
1479    local usetags = {
1480        ["circle"]             = true,
1481        ["ellipse"]            = true,
1482        ["g"]                  = true,
1483        ["image"]              = true,
1484        ["line"]               = true,
1485        ["path"]               = true,
1486        ["polygon"]            = true,
1487        ["polyline"]           = true,
1488        ["rect"]               = true,
1489     -- ["text"]               = true,
1490     -- ["tspan"]              = true,
1491    }
1492
1493    local pathtracer = {
1494        ["stroke"]         = "darkred",
1495        ["stroke-opacity"] = ".5",
1496        ["stroke-width"]   = ".5",
1497        ["fill"]           = "darkgray",
1498        ["fill-opacity"]   = ".75",
1499    }
1500
1501    local skipspace  = p_space^0
1502    local colon      = P(":")
1503    local semicolon  = P(";")
1504    local eos        = P(-1)
1505
1506    local someaction = (
1507        skipspace * C((1 - (skipspace * (semicolon + eos + colon)))^1)
1508      * colon
1509      * skipspace * C((1 - (skipspace * (semicolon + eos)))^0)
1510      * Carg(1) / function(k,v,a) a[k] = v end
1511        + (p_space + semicolon)^1
1512     )^1
1513
1514    local function handlechains(c)
1515        if tags[c.tg] then
1516            local at = c.at
1517            local dt = c.dt
1518            if at and dt then
1519             -- at["inkscape:connector-curvature"] = nil -- clear entry and might prevent table growth
1520                local estyle = rawget(at,"style")
1521                if estyle and estyle ~= "" then
1522                    lpegmatch(someaction,estyle,1,at)
1523                end
1524                local eclass = rawget(at,"class")
1525                if eclass and eclass ~= "" then
1526                    for c in gmatch(eclass,"[^ ]+") do
1527                        local s = classstyles[c]
1528                        if s then
1529                            for k, v in next, s do
1530                                at[k] = v
1531                            end
1532                        end
1533                    end
1534                end
1535                local tstyle = tagstyles[tag]
1536                if tstyle then
1537                    for k, v in next, tstyle do
1538                        at[k] = v
1539                    end
1540                end
1541                if trace_path and pathtracer then
1542                    for k, v in next, pathtracer do
1543                        at[k] = v
1544                    end
1545                end
1546                for i=1,#dt do
1547                    local dti = dt[i]
1548                    if type(dti) == "table" then
1549                        handlechains(dti)
1550                    end
1551                end
1552            end
1553        end
1554    end
1555
1556    local handlestyle  do
1557
1558        -- It can also be CDATA but that is probably dealt with because we only
1559        -- check for style entries and ignore the rest. But maybe we also need
1560        -- to check a style at the outer level?
1561
1562        local p_key   = C((R("az","AZ","09","__","--")^1))
1563        local p_spec  = P("{") * C((1-P("}"))^1) * P("}")
1564        local p_valid = Carg(1) * P(".") * p_key + Carg(2) * p_key
1565        local p_grab  = ((p_valid * p_space^0 * p_spec / rawset) + p_space^1 + P(1))^1
1566
1567        local fontspecification = css.fontspecification
1568
1569        handlestyle = function(c)
1570            local s = xmltext(c)
1571            lpegmatch(p_grab,s,1,classstyles,tagstyles)
1572            for k, v in next, classstyles do
1573                local t = { }
1574                for k, v in gmatch(v,"%s*([^:]+):%s*([^;]+);?") do
1575                    if k == "font" then
1576                        local s = fontspecification(v)
1577                        for k, v in next, s do
1578                            t["font-"..k] = v
1579                        end
1580                    else
1581                        t[k] = v
1582                    end
1583                end
1584                classstyles[k] = t
1585            end
1586            for k, v in next, tagstyles do
1587                local t = { }
1588                for k, v in gmatch(v,"%s*([^:]+):%s*([^;]+);?") do
1589                    if k == "font" then
1590                        local s = fontspecification(v)
1591                        for k, v in next, s do
1592                            t["font-"..k] = v
1593                        end
1594                    else
1595                        t[k] = v
1596                    end
1597                end
1598                tagstyles[k] = t
1599            end
1600        end
1601
1602        function handlers.style()
1603            -- ignore
1604        end
1605
1606    end
1607
1608    -- We can have root in definitions and then do a metatable lookup but use
1609    -- is not used that often I guess.
1610
1611    local function locate(id,c)
1612        if id == none then
1613            return
1614        end
1615        local res = definitions[id]
1616        local ref
1617        if res then
1618            return res
1619        end
1620        ref = gsub(id,"^url%(#(.-)%)$","%1")
1621        ref = gsub(ref,"^#","")
1622        -- we can make a fast id lookup
1623        res = xmlfirst(root,"**[@id='"..ref.."']")
1624        if res then
1625            definitions[id] = res
1626            return res
1627        end
1628        -- we expect resource paths to be specified but for now we want
1629        -- them on the same path .. we could use the url splitter .. todo
1630        ref = url.hashed(id)
1631        if not ref.nosheme and ref.scheme == "file" then
1632            local filename = ref.filename
1633            local fragment = ref.fragment
1634            if filename and filename ~= "" then
1635                local fullname = resolvers.findbinfile(filename)
1636                if lfs.isfile(fullname) then
1637                    report("loading use file: %s",fullname)
1638                    local root = xml.load(fullname)
1639                    res = xmlfirst(root,"**[@id='"..fragment.."']")
1640                    if res and c then
1641                        xmlinheritattributes(res,c) -- tricky
1642                        setmetatableindex(res.at,c.at)
1643                        definitions[id] = res
1644                        return res
1645                    end
1646                end
1647            end
1648        end
1649        return res
1650    end
1651
1652    -- also locate
1653
1654    local function handleclippath(at)
1655        local clippath = at["clip-path"]
1656
1657        if not clippath or clippath == "none" then
1658            return
1659        end
1660
1661        local spec = definitions[clippath] or locate(clippath)
1662
1663        -- do we really need this crap
1664        if not spec then
1665            local index = match(clippath,"(%d+)")
1666            if index then
1667                spec = xmlfirst(root,"clipPath["..tostring(tonumber(index) or 0).."]")
1668            end
1669        end
1670        -- so far for the crap
1671
1672        if not spec then
1673            report("unknown clip %a",clippath)
1674            return
1675        elseif spec.tg ~= "clipPath" then
1676            report("bad clip %a",clippath)
1677            return
1678        end
1679
1680      ::again::
1681        for c in xmlcollected(spec,"/(path|use|g)") do
1682            local tg = c.tg
1683            if tg == "use" then
1684                local ca = c.at
1685                local id = ca["xlink:href"]
1686                if id then
1687                    spec = locate(id)
1688                    if spec then
1689                        local sa = spec.at
1690                        setmetatableindex(sa,ca)
1691                        if spec.tg == "path" then
1692                            local d = sa.d
1693                            if d then
1694                                local p = grabpath(d)
1695                                p.evenodd = sa["clip-rule"] == "evenodd"
1696                                p.close = true
1697-- local transform = rawget(ca,"transform")
1698                                return p, clippath, transform
1699                            else
1700                                return
1701                            end
1702                        else
1703                            goto again
1704                        end
1705                    end
1706                end
1707             -- break
1708            elseif tg == "path" then
1709                local ca = c.at
1710                local d  = rawget(ca,"d")
1711                if d then
1712                    local p = grabpath(d)
1713                    p.evenodd = ca["clip-rule"] == "evenodd"
1714                    p.close   = true
1715                    local transform = rawget(ca,"transform")
1716                    if transform then
1717                        transform = handletransformstring(transform)
1718                    end
1719
1720local tr = rawget(at,"transform")
1721if tr then
1722    tr = handletransformstring(tr)
1723    if tr then
1724        if transform then
1725            transform = transform .. " " .. tr
1726        else
1727            transform = tr
1728        end
1729    end
1730end
1731
1732                    return p, clippath, transform
1733                else
1734                    return
1735                end
1736            else
1737                -- inherit?
1738            end
1739        end
1740    end
1741
1742    -- todo: clip = [ auto | rect(llx,lly,urx,ury) ]
1743
1744    local s_rotation_start <const> = "draw image ( "
1745    local f_rotation_stop          = formatters[") rotatedaround((0,0),-angle((%N,%N))) ;"]
1746    local f_rotation_angle         = formatters[") rotatedaround((0,0),-%N) ;"]
1747
1748    local s_offset_start   <const> = "draw image ( "
1749    local f_offset_stop            = formatters[") shifted (%N,%N) ;"]
1750    local s_size_start     <const> = "draw image ( "
1751    local f_size_stop              = formatters[") xysized (%N,%N) ;"]
1752
1753    local handleoffset, handlesize do
1754
1755        handleoffset = function(at)
1756            local x = asnumber_vx(rawget(at,"x"))
1757            local y = asnumber_vy(rawget(at,"y"))
1758            if x ~= 0 or y ~= 0 then
1759                return s_offset_start, f_offset_stop(x,y)
1760            end
1761        end
1762
1763        handlesize = function(at)
1764            local width  = asnumber_x(rawget(at,"width"))
1765            local height = asnumber_y(rawget(at,"height"))
1766            if width == 0 or height == 0 then
1767                -- bad scaling
1768            elseif width == 1 and height == 1 then
1769                -- no need for scaling
1770            else
1771                return s_size_start, f_size_stop(width,height)
1772            end
1773        end
1774
1775    end
1776
1777    function handlers.symbol(c)
1778        local at  = c.at
1779        -- x y refX refY
1780        local boffset, eoffset = handleoffset(at)
1781        local bsize, esize = handlesize(at)
1782        local btransform, etransform, transform = handletransform(at)
1783
1784        if boffset then
1785            r = r + 1 result[r] = boffset
1786        end
1787        if btransform then
1788            r = r + 1 result[r] = btransform
1789        end
1790        if bsize then
1791            r = r + 1 ; result[r] = bsize
1792        end
1793
1794-- local _x = at.x       at.x      = 0
1795-- local _y = at.y       at.y      = 0
1796-- local _w = at.width   at.width  = 0
1797-- local _h = at.height  at.height = 0
1798
1799        process(c,"/*")
1800-- at.x      = _x
1801-- at.y      = _y
1802-- at.width  = _w
1803-- at.height = _h
1804
1805        if esize then
1806            r = r + 1 result[r] = esize
1807        end
1808        if etransform then
1809            r = r + 1 ; result[r] = etransform
1810        end
1811        if eoffset then
1812            r = r + 1 result[r] = eoffset
1813        end
1814    end
1815
1816    -- do
1817
1818    local s_shade_linear   =            '    withshademethod "linear" '
1819    local s_shade_circular =            '    withshademethod "circular" '
1820    local f_color          = formatters['    withcolor "%s"']
1821    local f_opacity        = formatters['    withopacity %N']
1822    local f_pen            = formatters['    withpen pencircle scaled %N']
1823
1824    -- this is rather hard to deal with because browsers differ (at the time of writing)
1825    -- and what they show on screen comes out different (or not at all) in print
1826
1827    -- todo: gradientUnits = "userSpaceOnUse" : use units instead of ratios
1828
1829    -- spreadMethod = "pad"     : default
1830    -- spreadMethod = "repeat"  : crap
1831    -- spreadMethod = "reflect" : crap
1832
1833    -- stop-opacity = "0"       : strange, just use steps for that
1834
1835    -- todo: test for kind independently in caller, make a plug instead
1836
1837    local function pattern(id)
1838        local c = definitions[id] -- no locate !
1839        if c and c.tg == "pattern" then
1840            -- just use result and then prune
1841            local _r      = r
1842            local _result = result
1843            r      = 0
1844            result = { }
1845            --
1846         -- handlers.pattern(spec)
1847            --
1848            -- inlined because of width
1849            --
1850            local at  = c.at
1851
1852            local width  = asnumber_x(rawget(at,"width"))
1853            local height = asnumber_y(rawget(at,"height"))
1854            if width == 0 or height == 0 then
1855                -- bad scaling
1856                width  = nil
1857                height = nil
1858            elseif width == 1 and height == 1 then
1859                -- no need for scaling
1860                width  = nil
1861                height = nil
1862            else
1863                -- for now only relative
1864            end
1865
1866            local boffset, eoffset = handleoffset(at)
1867         -- local bsize, esize = handlesize(at)
1868            local btransform, etransform, transform = handletransform(at)
1869
1870            if boffset then
1871                r = r + 1 result[r] = boffset
1872            end
1873            if btransform then
1874                r = r + 1 result[r] = btransform
1875            end
1876         -- if bsize then
1877         --     r = r + 1 ; result[r] = bsize
1878         -- end
1879
1880            local _x = at.x       at.x      = 0
1881            local _y = at.y       at.y      = 0
1882            local _w = at.width   at.width  = 0
1883            local _h = at.height  at.height = 0
1884
1885            process(c,"/*")
1886
1887            at.x      = _x
1888            at.y      = _y
1889            at.width  = _w
1890            at.height = _h
1891
1892         -- if esize then
1893         --     r = r + 1 result[r] = esize
1894         -- end
1895            if etransform then
1896                r = r + 1 ; result[r] = etransform
1897            end
1898            if eoffset then
1899                r = r + 1 result[r] = eoffset
1900            end
1901            --
1902            local okay
1903            if width and height then
1904                okay = formatters["    withpattern image ( % t )\n    withpatternscale(%N,%N)"](result,width,height)
1905            else
1906                okay = formatters["    withpattern image ( % t )"](result)
1907            end
1908            r      = _r
1909            result = _result
1910            return okay
1911        end
1912    end
1913
1914    local gradient do
1915
1916        local f_shade_step         = formatters['    withshadestep ( withshadefraction %N withshadecolors (%s,%s) )']
1917        local f_shade_colors       = formatters['    withshadecolors (%s,%s)']
1918        local f_shade_center       = formatters['    withshadecenter (%N,%N)']
1919        local f_shade_center_f     = formatters['    withshadecenterfraction (%N,%N)']
1920        local f_shade_radius       = formatters['    withshaderadius (%N,%N) ']
1921        local f_shade_radius_f     = formatters['    withshaderadiusfraction %N']
1922        local f_shade_center_one   = formatters['    withshadecenterone (%N,%N)']
1923        local f_shade_center_two   = formatters['    withshadecentertwo (%N,%N)']
1924        local f_shade_center_one_f = formatters['    withshadecenteronefraction (%N,%N)']
1925        local f_shade_center_two_f = formatters['    withshadecentertwofraction (%N,%N)']
1926        local f_shade_transform    = formatters['    withshadetransformation identity %s']
1927
1928        local f_shade_inverse      = formatters[' transformed inverse (identity %s)']
1929--         local f_shade_inverse      = formatters[' transformed inverse identity %s'] -- or this?
1930
1931        gradient = function(id)
1932            local spec = definitions[id] -- no locate !
1933            if spec then
1934                local kind  = spec.tg
1935                local shade = { }
1936                local opacs = nil
1937                local ns    = 0
1938                local no    = 0
1939                local a     = spec.at
1940                -- bah
1941                local hid = rawget(a,"href") or rawget(a,"xlink:href") -- better a rawget
1942                local res = locate(hid)
1943                -- bah
1944                local gu = rawget(a, "gradientUnits")         -- userSpaceOnUse
1945                local gt = rawget(a, "gradientTransform")
1946                local sm = rawget(a, "spreadMethod")
1947                --
1948                local userspace = gu == "userSpaceOnUse"
1949                --
1950                if kind == "linearGradient" then
1951                    ns = ns + 1 ; shade[ns] = s_shade_linear
1952                    --
1953                    local x1 = rawget(a,"x1")
1954                    local y1 = rawget(a,"y1")
1955                    local x2 = rawget(a,"x2")
1956                    local y2 = rawget(a,"y2")
1957                    if userspace then
1958                        if x1 and y1 then
1959                            ns = ns + 1 ; shade[ns] = f_shade_center_one(asnumber_p(x1),asnumber_p(y1))
1960                        end
1961                        if x2 and y2 then
1962                            ns = ns + 1 ; shade[ns] = f_shade_center_two(asnumber_p(x2),asnumber_p(y2))
1963                        end
1964                    else
1965                        if x1 and y1 then
1966                            ns = ns + 1 ; shade[ns] = f_shade_center_one_f(asnumber_p(x1),1-asnumber_p(y1))
1967                        end
1968                        if x2 and y2 then
1969                            ns = ns + 1 ; shade[ns] = f_shade_center_two_f(asnumber_p(x2),1-asnumber_p(y2))
1970                        end
1971                    end
1972                    --
1973                elseif kind == "radialGradient" then
1974                    ns = ns + 1 ; shade[ns] = s_shade_circular
1975                    --
1976                    local cx = rawget(a,"cx") -- x center
1977                    local cy = rawget(a,"cy") -- y center
1978                    local r  = rawget(a,"r" ) -- radius
1979                    local fx = rawget(a,"fx") -- focal points
1980                    local fy = rawget(a,"fy") -- focal points
1981                    --
1982                    if userspace then
1983                        if cx and cy then
1984                            ns = ns + 1 ; shade[ns] = f_shade_center(asnumber_p(cx),asnumber_p(cy))
1985                        end
1986                        if fx and fy then
1987                            ns = ns + 1 ; shade[ns] = f_shade_center_one(asnumber_p(fx),-asnumber_p(fy))
1988                        end
1989                        if r then
1990                            ns = ns + 1 ; shade[ns] = f_shade_radius(asnumber_p(r))
1991                        end
1992                        if fx and fy then
1993                            -- todo
1994                        end
1995                    else
1996                        if cx and cy then
1997                            ns = ns + 1 ; shade[ns] = f_shade_center_f(asnumber_p(cx),1-asnumber_p(cy))
1998                        end
1999                        if fx and fy then
2000                            ns = ns + 1 ; shade[ns] = f_shade_center_one_f(asnumber_p(fx),1-asnumber_p(fy))
2001                        end
2002                        if r then
2003                            ns = ns + 1 ; shade[ns] = f_shade_radius_f(asnumber_p(r))
2004                        end
2005                        if fx and fy then
2006                            -- todo
2007                        end
2008                    end
2009                else
2010                    return
2011                end
2012                -- startcolor ?
2013                local function crap(spec)
2014                    local colora, colorb
2015                    local opacitya, opacityb
2016                    local lastns = ns
2017                    for c in xmlcollected(spec,"/stop") do
2018                        local a      = c.at
2019                        local offset = rawget(a,"offset")
2020                        local colorb = rawget(a,"stop-color")
2021                        if not colora then
2022                            colora = colorb
2023                        end
2024                        -- what if no percentage
2025                     -- local fraction = offset and asnumber_r(offset) -- asnumber_p ?
2026                        local fraction = offset and asnumber_p(offset)
2027                        if not fraction then
2028                            -- for now
2029                            fraction = xmlcount(spec,"/stop")/100      -- asnumber_p ?
2030                        end
2031                        if colora and colorb and colora ~= "" and colorb ~= "" then
2032                            ns = ns + 1
2033                            if userspace then -- todo
2034                                shade[ns] = f_shade_step(fraction,thecolor(colora),thecolor(colorb))
2035                            else
2036                                shade[ns] = f_shade_step(fraction,thecolor(colora),thecolor(colorb))
2037                            end
2038                        end
2039                        colora = colorb
2040                    end
2041                    for c in xmlcollected(spec,"/stop[@stop-opacity]") do
2042                        opacityb = c.at["stop-opacity"]
2043                        if not opacitya then
2044                            opacitya = opacityb
2045                        end
2046                    end
2047                    if opacitya then
2048                        opacs = { }
2049                        for i=1,lastns do
2050                            no = no + 1 ; opacs[no] = shade[i]
2051                        end
2052                        no = no + 1 ; opacs[no] = f_shade_colors(opacitya,opacityb)
2053                    end
2054                    return colora
2055                end
2056                --
2057                if not crap(spec) then
2058                    -- for now but maybe we need more
2059                 -- local id  = rawget(a,"href") or rawget(a,"xlink:href") -- better a rawget
2060                 -- local res = locate(id,c)
2061                    if res then
2062                        crap(res)
2063                    end
2064                end
2065                local transform
2066                if gt then
2067                    ns = ns + 1
2068                    transform = handletransformstring(gt)
2069                    shade[ns] = f_shade_transform(transform)
2070                    transform = f_shade_inverse(transform)
2071                    if opacitya then
2072                        no = no + 1
2073                        opacs[no] = shade[no]
2074                    end
2075                end
2076                shade = concat(shade,"\n    ")
2077                opacs = no > 0 and concat(opacs,"\n    ")
2078                return shade, opacs, transform
2079            end
2080        end
2081    end
2082
2083    local function drawproperties(stroke,at,opacity)
2084        local p = at["stroke-width"]
2085        if p then
2086            p = f_pen(asnumber_r(p))
2087        end
2088        local d = at["stroke-dasharray"]
2089        if d == "none" then
2090            d = nil
2091        elseif d then
2092            local o = at["stroke-dashoffset"]
2093            if o and o ~= "none" then
2094                o = asnumber_r(o)
2095            else
2096                o = false
2097            end
2098            d = dashed(d,o)
2099        end
2100        local c = withcolor(stroke)
2101        local o = at["stroke-opacity"] or (opacity and at["opacity"])
2102        if o == "none" then
2103            o = nil
2104        elseif o == "transparent" then
2105            o = f_opacity(0)
2106        elseif o then
2107            o = asnumber_r(o)
2108            if o == ignoredopacity then
2109                o = nil
2110            elseif o then
2111                o = f_opacity(o)
2112            else
2113                o = nil
2114            end
2115        end
2116        return p, d, c, o
2117    end
2118
2119    local s_opacity_start   <const> = "draw image ("
2120    local f_opacity_content         = formatters["setgroup currentpicture to boundingbox currentpicture withopacity %N;"]
2121    local s_opacity_stop    <const> = ") ;"
2122
2123    local function sharedopacity(at)
2124        local o = at["opacity"]
2125        if o and o ~= "none" then
2126            o = asnumber_r(o)
2127            if o == ignoredopacity then
2128                return
2129            end
2130            if o then
2131                return s_opacity_start, f_opacity_content(o), s_opacity_stop
2132            end
2133        end
2134    end
2135
2136    -- it looks like none and transparent are both used (mozilla examples)
2137
2138    local function fillproperties(fill,at,opacity)
2139     -- local o = at["fill-opacity"] or (opacity and at["opacity"])
2140        local o = at["fill-opacity"] or (opacity and rawget(at,"opacity")) -- opacity not inherited as it can be on the group
2141        -- what a mess ... examples and suggestions are not consistent
2142        local o = at["fill-opacity"]
2143        if tonumber(o) == 1 then
2144            -- so kind of unset
2145            o = rawget(at,"opacity") or o
2146        end
2147        --
2148        local c   = nil
2149        local t   = nil
2150        local ops = nil
2151        if c ~= "none" then
2152            c, ops, t = gradient(fill)
2153            if ops then
2154                return c, ops, t
2155            end
2156            if not c then
2157                c = pattern(fill)
2158                if c then
2159                    if o and o ~= "none" then
2160                        o = asnumber_r(o)
2161                        if o ~= ignoredopacity then
2162                            return c, ops, t, f_opacity(o), "pattern"
2163                        end
2164                    end
2165                    return c, ops, t, false, "pattern"
2166                else
2167                    c = withcolor(fill)
2168                end
2169            end
2170        end
2171        if not o and fill == "transparent" then
2172            return nil, nil, nil, f_opacity(0), true
2173        elseif o and o ~= "none" then
2174            o = asnumber_r(o)
2175            if o == ignoredopacity then
2176                return c, nil, t
2177            end
2178            if o then
2179                return c, nil, t, f_opacity(o), (o == 1 and "invisible")
2180            end
2181        end
2182        return c, ops, t
2183    end
2184
2185    local viewport do
2186
2187        local s_viewport_start  <const> = "draw image ("
2188        local s_viewport_stop   <const> = ") ;"
2189        local f_viewport_shift          = formatters["currentpicture := currentpicture shifted (%N,%N);"]
2190        local f_viewport_scale          = formatters["currentpicture := currentpicture xysized (%N,%N);"]
2191        local f_viewport_clip           = formatters["clip currentpicture to (unitsquare xyscaled (%N,%N));"]
2192
2193        viewport = function(x,y,w,h,noclip,scale)
2194            r = r + 1 ; result[r] = s_viewport_start
2195            return function()
2196                local okay = w ~= 0 and h ~= 0
2197                if okay and scale then
2198                    r = r + 1 ; result[r] = f_viewport_scale(w,h)
2199                end
2200                if x ~= 0 or y ~= 0 then
2201                    r = r + 1 ; result[r] = f_viewport_shift(-x,y)
2202                end
2203                if okay and not noclip then
2204                    r = r + 1 ; result[r] = f_viewport_clip(w,-h)
2205                end
2206
2207                r = r + 1 ; result[r] = s_viewport_stop
2208            end
2209        end
2210
2211    end
2212
2213    -- maybe forget about defs and just always locate (and then backtrack
2214    -- over <g> if needed) .. so, only store after locating
2215
2216    function handledefinitions(c)
2217        for c in xmlcollected(c,"defs/*") do
2218            local a = c.at
2219            if a then
2220                local id = rawget(a,"id")
2221                if id then
2222                    definitions["#"     .. id       ] = c
2223                    definitions["url(#" .. id .. ")"] = c
2224                end
2225            end
2226        end
2227        for c in xmlcollected(c,"(symbol|radialGradient|linearGradient)") do
2228            local id = rawget(c.at,"id")
2229            if id then
2230                definitions["#"     .. id       ] = c
2231                definitions["url(#" .. id .. ")"] = c
2232            end
2233        end
2234    end
2235
2236 --  function handlers.defs(c)
2237 --     for c in xmlcollected(c,"/*") do
2238 --         local a = c.at
2239 --         if a then
2240 --             local id = rawget(a,"id")
2241 --             if id then
2242 --                 definitions["#"     .. id       ] = c
2243 --                 definitions["url(#" .. id .. ")"] = c
2244 --             end
2245 --         end
2246 --     end
2247 -- end
2248
2249    -- lots of stuff todo: transform
2250
2251    local uselevel = 0
2252
2253    function handlers.use(c)
2254        local at  = c.at
2255        local id  = rawget(at,"href") or rawget(at,"xlink:href") -- better a rawget
2256        local res = locate(id,c)
2257        if res then
2258            uselevel = uselevel + 1
2259            local boffset, eoffset = handleoffset(at)
2260            local btransform, etransform, transform = handletransform(at)
2261
2262            if boffset then
2263                r = r + 1 result[r] = boffset
2264            end
2265
2266         -- local clippath  = at.clippath
2267
2268            if btransform then
2269                r = r + 1 result[r] = btransform
2270            end
2271
2272            local _transform = transform
2273            local _clippath  = clippath
2274            at["transform"] = false
2275         -- at["clip-path"] = false
2276
2277            setmetatableindex(res.at,at)
2278
2279            local tg = res.tg
2280         -- if usetags[tg] then
2281                process(res,".")
2282         -- else
2283         --     process(res,"/*")
2284         -- end
2285
2286            at["transform"] = _transform
2287         -- at["clip-path"] = _clippath
2288
2289            if etransform then
2290                r = r + 1 ; result[r] = etransform
2291            end
2292
2293            if eoffset then
2294                r = r + 1 result[r] = eoffset
2295            end
2296
2297            uselevel = uselevel - 1
2298        else
2299            report("use: unknown definition %a",id)
2300        end
2301    end
2302
2303    local f_do_draw               = formatters['  draw (%s)']
2304    local f_do_fill               = formatters['  fill (%s)']
2305    local f_eo_fill               = formatters['  eofill (%s)']
2306    local s_clip_start    <const> = 'save p ; picture p ; p := image ('
2307    local f_clip_stop_c           = formatters[') ; clip p to (%s &&& cycle) %s ; draw p ;']
2308    local f_clip_stop_l           = formatters[') ; clip p to (%s &&& cycle) %s ; draw p ;']
2309    local f_clip_stop             = f_clip_stop_c
2310    local f_eoclip_stop_c         = formatters[') ; eoclip p to (%s &&& cycle) %s ; draw p ;']
2311    local f_eoclip_stop_l         = formatters[') ; eoclip p to (%s &&& cycle) %s ; draw p ;']
2312    local f_eoclip_stop           = f_eoclip_stop_c
2313
2314    local f_shade_luminosity      = formatters['draw luminosityshade (\n  (%s &&& cycle) %s\n  ) (\n%s\n  ) (\n%s\n) ;']
2315
2316    -- could be shared and then beginobject | endobject
2317
2318    local function flushobject(object,at,c,o)
2319        local btransform, etransform = handletransform(at)
2320        local cpath, _, ctransform = handleclippath(at)
2321
2322        if cpath then
2323            r = r + 1 ; result[r] = s_clip_start
2324        end
2325
2326        if btransform then
2327            r = r + 1 ; result[r] = btransform
2328        end
2329
2330        r = r + 1 ; result[r] = f_do_draw(object)
2331
2332        if c then
2333            r = r + 1 ; result[r] = c
2334        end
2335
2336        if o then
2337            r = r + 1 ; result[r] = o
2338        end
2339
2340        if etransform then
2341            r = r + 1 ; result[r] = etransform
2342        end
2343
2344        r = r + 1 ; result[r] = "  ;"
2345
2346        if cpath then
2347            local f_done = cpath.evenodd
2348            if cpath.curve then
2349                f_done = f_done and f_eoclip_stop_c or f_clip_stop_c
2350            else
2351                f_done = f_done and f_eoclip_stop_l or f_clip_stop_l
2352            end
2353            r = r + 1 ; result[r] = f_done(cpath.path,ctransform or "")
2354        end
2355
2356        if etransform then
2357            r = r + 1 ; result[r] = etransform
2358        end
2359    end
2360
2361    do
2362
2363        local flush
2364
2365        local f_withlinecap    = formatters["    withlinecap %s"]
2366        local f_withlinejoin   = formatters["    withlinejoin %s"]
2367        local f_withmiterlimit = formatters["    withmiterlimit %s;"]
2368
2369        local linecaps  = { butt  = "butt",    square = "squared", round = "rounded" }
2370        local linejoins = { miter = "mitered", bevel  = "beveled", round = "rounded" }
2371
2372        local function lineproperties(at)
2373            local cap   = at["stroke-linecap"]
2374            local join  = at["stroke-linejoin"]
2375            local limit = at["stroke-miterlimit"]
2376            if cap then
2377                cap = linecaps[cap]
2378            end
2379            if join then
2380                join = linejoins[join]
2381            end
2382            if limit then
2383                limit = asnumber_r(limit)
2384            end
2385            return cap, join, limit
2386        end
2387
2388        -- markers are a quite rediculous thing .. let's assume simple usage for now
2389
2390        function handlers.marker()
2391            -- todo: is just a def too
2392        end
2393
2394        -- kind of local svg ... so make a generic one
2395        --
2396        -- todo: combine more (offset+scale+rotation)
2397
2398        local function makemarker(where,c,x1,y1,x2,y2,x3,y3,parentat)
2399            local at     = c.at
2400            local refx   = rawget(at,"refX")
2401            local refy   = rawget(at,"refY")
2402            local width  = rawget(at,"markerWidth")
2403            local height = rawget(at,"markerHeight")
2404            local units  = rawget(at,"markerUnits") -- no parentat["stroke-width"], bad for m4mbo
2405            local view   = rawget(at,"viewBox")
2406            local orient = rawget(at,"orient")
2407         -- local ratio  = rawget(at,"preserveAspectRatio")
2408            local units  = units and asnumber(units) or 1
2409
2410            local angx   = 0
2411            local angy   = 0
2412            local angle  = 0
2413
2414            if where == "beg" then
2415                if orient == "auto" then -- unchecked
2416                    -- no angle
2417                    angx = abs(x2 - x3)
2418                    angy = abs(y2 - y3)
2419                elseif orient == "auto-start-reverse" then -- checked
2420                    -- points to start
2421                    angx = -abs(x2 - x3)
2422                    angy = -abs(y2 - y3)
2423                elseif orient then -- unchecked
2424                    angle = asnumber_r(orient)
2425                end
2426            elseif where == "end" then
2427                -- funny standard .. bug turned feature?
2428                if orient == "auto" or orient == "auto-start-reverse" then
2429                    angx = abs(x1 - x2)
2430                    angy = abs(y1 - y2)
2431                elseif orient then -- unchecked
2432                    angle = asnumber_r(orient)
2433                end
2434            elseif orient then -- unchecked
2435                angle = asnumber_r(orient)
2436            end
2437            -- what wins: viewbox or w/h
2438
2439            refx = asnumber_x(refx)
2440            refy = asnumber_y(refy)
2441
2442            width  = (width  and asnumber_x(width)  or 3) * units
2443            height = (height and asnumber_y(height) or 3) * units
2444
2445            local x = 0
2446            local y = 0
2447            local w = width
2448            local h = height
2449
2450            -- kind of like the main svg
2451
2452            r = r + 1 ; result[r] = s_offset_start
2453
2454            local wrapupviewport
2455
2456            -- todo : better viewbox code
2457
2458            local xpct, ypct, rpct
2459            if view then
2460                x, y, w, h = handleviewbox(view)
2461            end
2462
2463            if width ~= 0 then
2464                w = width
2465            end
2466            if height ~= 0 then
2467                h = height
2468            end
2469
2470            if h then
2471                xpct           = percentage_x
2472                ypct           = percentage_y
2473                rpct           = percentage_r
2474                percentage_x   = w / 100
2475                percentage_y   = h / 100
2476                percentage_r   = (sqrt(w^2 + h^2) / sqrt(2)) / 100
2477                wrapupviewport = viewport(x,y,w,h,true,true) -- no clip
2478            end
2479
2480            -- we can combine a lot here:
2481
2482            local hasref = refx ~= 0 or refy ~= 0
2483            local hasrot = angx ~= 0 or angy ~= 0 or angle ~= 0
2484
2485            local btransform, etransform, transform = handletransform(at)
2486
2487            if btransform then
2488                r = r + 1 ; result[r] = btransform
2489            end
2490
2491            if hasrot then
2492                r = r + 1 ; result[r] = s_rotation_start
2493            end
2494
2495            if hasref then
2496                r = r + 1 ; result[r] = s_offset_start
2497            end
2498
2499            local _transform = transform
2500            at["transform"] = false
2501
2502            handlers.g(c)
2503
2504            at["transform"] = _transform
2505
2506            if hasref then
2507                r = r + 1 ; result[r] = f_offset_stop(-refx,refy)
2508            end
2509
2510            if hasrot then
2511                if angle ~= 0 then
2512                    r = r + 1 ; result[r] = f_rotation_angle(angle)
2513                else
2514                    r = r + 1 ; result[r] = f_rotation_stop(angx,angy)
2515                end
2516            end
2517
2518            if etransform then
2519                r = r + 1 ; result[r] = etransform
2520            end
2521
2522            if h then
2523                percentage_x = xpct
2524                percentage_y = ypct
2525                percentage_r = rpct
2526                if wrapupviewport then
2527                    wrapupviewport()
2528                end
2529            end
2530            r = r + 1 ; result[r] = f_offset_stop(x2,y2)
2531
2532        end
2533
2534        -- do we need to metatable the attributes here?
2535
2536        local function addmarkers(list,begmarker,midmarker,endmarker,at)
2537            local n = #list
2538            if n > 3 then
2539                if begmarker then
2540                    local m = locate(begmarker)
2541                    if m then
2542                        makemarker("beg",m,false,false,list[1],list[2],list[3],list[4],at)
2543                    end
2544                end
2545                if midmarker then
2546                    local m = locate(midmarker)
2547                    if m then
2548                        for i=3,n-2,2 do
2549                            makemarker("mid",m,list[i-2],list[i-1],list[i],list[i+1],list[i+2],list[i+3],at)
2550                        end
2551                    end
2552                end
2553                if endmarker then
2554                    local m = locate(endmarker)
2555                    if m then
2556                        makemarker("end",m,list[n-3],list[n-2],list[n-1],list[n],false,false,at)
2557                    end
2558                end
2559            else
2560                -- no line
2561            end
2562        end
2563
2564        local function flush(shape,dofill,closed,at,list,begmarker,midmarker,endmarker)
2565            local fill   = dofill and (at["fill"] or "black")
2566            local stroke = at["stroke"] or "none"
2567
2568            local btransform, etransform = handletransform(at)
2569            local cpath, _, ctransform = handleclippath(at)
2570
2571            if cpath then
2572                r = r + 1 ; result[r] = s_clip_start
2573            end
2574
2575            local has_stroke = stroke and stroke ~= "none"
2576            local has_fill   = fill and fill ~= "none"
2577
2578            local bopacity, copacity, eopacity
2579            if has_stroke and has_fill then
2580                bopacity, copacity, eopacity = sharedopacity(at)
2581            end
2582            if copacity then
2583                r = r + 1 ; result[r] = bopacity
2584            end
2585            if has_fill and not closed then
2586                shape = shape .. "&&cycle"
2587            end
2588            if has_fill then
2589                local color, opacs, transform, opacity, option = fillproperties(fill,at,not has_stroke)
2590                local f_xx_fill = at["fill-rule"] == "evenodd" and f_eo_fill or f_do_fill
2591                if option ~= pattern and opacs then
2592                 -- btransform or "",
2593                 -- etransform or "",
2594                    r = r + 1 ; result[r] = f_shade_luminosity(shape,transform or "",opacs,color)
2595                else
2596                    if btransform then
2597                        r = r + 1 ; result[r] = btransform
2598                    end
2599                    if option == "pattern" then
2600                        r = r + 1 ; result[r] = f_d_draw(shape)
2601                    else
2602                        r = r + 1 ; result[r] = f_xx_fill(shape)
2603                        if transform then
2604                            r = r + 1 result[r] = transform
2605                        end
2606                    end
2607                    if color   then
2608                        r = r + 1 ; result[r] = color
2609                    end
2610                    if opacity then
2611                        r = r + 1 ; result[r] = opacity
2612                    end
2613                    r = r + 1 ; result[r] = etransform or "  ;"
2614                end
2615            end
2616
2617            if has_stroke then
2618                local pen, dashing, color, opacity = drawproperties(stroke,at,not has_fill)
2619                local cap, join, limit = lineproperties(at)
2620                if btransform then
2621                    r = r + 1 ; result[r] = btransform
2622                end
2623                r = r + 1 ; result[r] = f_do_draw(shape)
2624                if pen     then r = r + 1 ; result[r] = pen     end
2625                if dashing then r = r + 1 ; result[r] = dashing end
2626                if color   then r = r + 1 ; result[r] = color   end
2627                if opacity then r = r + 1 ; result[r] = opacity end
2628                if cap     then r = r + 1 ; result[r] = f_withlinecap   (cap)   end
2629                if join    then r = r + 1 ; result[r] = f_withlinejoin  (join)  end
2630                if limit   then r = r + 1 ; result[r] = f_withmiterlimit(limit) end
2631                r = r + 1 ; result[r] = etransform or "  ;"
2632                --
2633                if list then
2634                    addmarkers(list,begmarker,midmarker,endmarker,at)
2635                end
2636            end
2637            if copacity then
2638                r = r + 1 ; result[r] = copacity
2639                r = r + 1 ; result[r] = eopacity
2640            end
2641
2642            if cpath then
2643                r = r + 1 ; result[r] = (cpath.evenodd and f_eoclip_stop or f_clip_stop)(cpath.path,ctransform)
2644            end
2645        end
2646
2647        local f_rectangle = formatters['unitsquare xyscaled (%N,%N) shifted (%N,%N)']
2648        local f_rounded   = formatters['roundedsquarexy(%N,%N,%N,%N) shifted (%N,%N)']
2649        local f_line      = formatters['((%N,%N)--(%N,%N))']
2650        local f_ellipse   = formatters['(fullcircle xyscaled (%N,%N) shifted (%N,%N))']
2651        local f_circle    = formatters['(fullcircle scaled %N shifted (%N,%N))']
2652
2653        function handlers.line(c)
2654            local at = c.at
2655            local x1 = rawget(at,"x1")
2656            local y1 = rawget(at,"y1")
2657            local x2 = rawget(at,"x2")
2658            local y2 = rawget(at,"y2")
2659
2660            x1 = x1 and asnumber_vx(x1) or 0
2661            y1 = y1 and asnumber_vy(y1) or 0
2662            x2 = x2 and asnumber_vx(x2) or 0
2663            y2 = y2 and asnumber_vy(y2) or 0
2664
2665            flush(f_line(x1,y1,x2,y2),false,false,at)
2666        end
2667
2668        function handlers.rect(c)
2669            local at     = c.at
2670            local width  = rawget(at,"width")
2671            local height = rawget(at,"height")
2672            local x      = rawget(at,"x")
2673            local y      = rawget(at,"y")
2674            local rx     = rawget(at,"rx")
2675            local ry     = rawget(at,"ry")
2676
2677            width  = width  and asnumber_x(width)  or 0
2678            height = height and asnumber_y(height) or 0
2679            x      = x      and asnumber_vx(x) or 0
2680            y      = y      and asnumber_vy(y) or 0
2681
2682            y      = y - height
2683
2684            if rx then rx = asnumber_x(rx) end
2685            if ry then ry = asnumber_y(ry) end
2686
2687            if rx or ry then
2688                if not rx then rx = ry end
2689                if not ry then ry = rx end
2690                flush(f_rounded(width,height,rx,ry,x,y),true,true,at)
2691            else
2692                flush(f_rectangle(width,height,x,y),true,true,at)
2693            end
2694        end
2695
2696        function handlers.ellipse(c)
2697            local at = c.at
2698            local cx = rawget(at,"cx")
2699            local cy = rawget(at,"cy")
2700            local rx = rawget(at,"rx")
2701            local ry = rawget(at,"ry")
2702
2703            cx = cx and asnumber_vx(cx) or 0
2704            cy = cy and asnumber_vy(cy) or 0
2705            rx = rx and asnumber_r (rx) or 0
2706            ry = ry and asnumber_r (ry) or 0
2707
2708            flush(f_ellipse(2*rx,2*ry,cx,cy),true,true,at)
2709        end
2710
2711        function handlers.circle(c)
2712            local at = c.at
2713            local cx = rawget(at,"cx")
2714            local cy = rawget(at,"cy")
2715            local r  = rawget(at,"r")
2716
2717            cx = cx and asnumber_vx(cx) or 0
2718            cy = cy and asnumber_vy(cy) or 0
2719            r  = r  and asnumber_r (r)  or 0
2720
2721            flush(f_circle(2*r,cx,cy),true,true,at)
2722        end
2723
2724        local f_lineto_z  = formatters['(%N,%N)']
2725        local f_lineto_n  = formatters['--(%N,%N)']
2726
2727        local p_pair     = p_optseparator * p_number_vx * p_optseparator * p_number_vy
2728        local p_open     = Cc("(")
2729        local p_close    = Carg(1) * P(true) / function(s) return s end
2730        local p_polyline = Cs(p_open * (p_pair / f_lineto_z) * (p_pair / f_lineto_n)^0 * p_close)
2731        local p_polypair = Ct(p_pair^0)
2732
2733        local function poly(c,final)
2734            local at     = c.at
2735            local points = rawget(at,"points")
2736            if points then
2737                local path = lpegmatch(p_polyline,points,1,final)
2738                local list = nil
2739                local begmarker = rawget(at,"marker-start")
2740                local midmarker = rawget(at,"marker-mid")
2741                local endmarker = rawget(at,"marker-end")
2742                if begmarker or midmarker or endmarker then
2743                    list = lpegmatch(p_polypair,points)
2744                end
2745                -- check closed
2746                flush(path,true,false,at,list,begmarker,midmarker,endmarker)
2747            end
2748        end
2749
2750        function handlers.polyline(c) poly(c,       ")") end
2751        function handlers.polygon (c) poly(c,"--cycle)") end
2752
2753        function handlers.path(c)
2754            local at = c.at
2755            local d  = rawget(at,"d")
2756            if d then
2757                local shape, l = grabpath(d)
2758                local path     = shape.path
2759                if not path or #path == "" then
2760                    return
2761                end
2762                local fill   = at["fill"] or "black"
2763                local stroke = at["stroke"] or "none"
2764                local btransform, etransform = handletransform(at)
2765                local cpath, _, ctransform = handleclippath(at)
2766                if cpath then
2767                    r = r + 1 ; result[r] = s_clip_start
2768                end
2769
2770                -- todo: image (nicer for transform too)
2771
2772                if fill and fill ~= "none" then
2773                    local color, opacs, transform, opacity, option = fillproperties(fill,at)
2774                    local evenodd = at["fill-rule"] == "evenodd"
2775                    if not shape.closed then
2776                        path = path .. "&&cycle"
2777                    end
2778                    if opacs then
2779                     -- btransform or "",
2780                     -- etransform or "",
2781                        r = r + 1 ; result[r] = f_shade_luminosity(path,transform or "",opacs,color)
2782                    else
2783                        if btransform then
2784                            r = r + 1 ; result[r] = btransform
2785                        end
2786                        if option == "pattern" then
2787                            r = r + 1 result[r] = f_do_draw(path)
2788                        elseif evenodd then
2789                            r = r + 1 result[r] = f_eo_fill(path)
2790                        else
2791                            r = r + 1 result[r] = f_do_fill(path)
2792                        end
2793                        if color then
2794                            r = r + 1 ; result[r] = color
2795                        end
2796                        if opacity then
2797                            r = r + 1 ; result[r] = opacity
2798                        end
2799                        r = r + 1 ; result[r] = etransform or "  ;"
2800                    end
2801                end
2802
2803                if stroke and stroke ~= "none" then
2804                    local begmarker = rawget(at,"marker-start")
2805                    local midmarker = rawget(at,"marker-mid")
2806                    local endmarker = rawget(at,"marker-end")
2807                    if begmarker or midmarker or endmarker then
2808                        list = grablist(l)
2809                    end
2810                    local pen, dashing, color, opacity = drawproperties(stroke,at)
2811                    local cap, join, limits = lineproperties(at)
2812                    if btransform then
2813                        r = r + 1 ; result[r] = btransform
2814                    end
2815                    r = r + 1 result[r] = f_do_draw(path)
2816                    if pen     then r = r + 1 ; result[r] = pen     end
2817                    if dashing then r = r + 1 ; result[r] = dashing end
2818                    if color   then r = r + 1 ; result[r] = color   end
2819                    if opacity then r = r + 1 ; result[r] = opacity end
2820                    if cap     then r = r + 1 ; result[r] = f_withlinecap   (cap)   end
2821                    if join    then r = r + 1 ; result[r] = f_withlinejoin  (join)  end
2822                    if limit   then r = r + 1 ; result[r] = f_withmiterlimit(limit) end
2823                    r = r + 1 result[r] = etransform or "  ;"
2824                    if list then
2825                        addmarkers(list,begmarker,midmarker,endmarker,at)
2826                    end
2827                end
2828
2829                if cpath then
2830                    r = r + 1 ; result[r] = f_clip_stop(cpath.path,ctransform)
2831                end
2832            end
2833        end
2834
2835    end
2836
2837    -- kind of special
2838
2839    do
2840
2841        -- some day:
2842        --
2843        -- specification = identifiers.jpg(data."string")
2844        -- specification.data = data
2845        -- inclusion takes from data
2846        -- specification.data = false
2847
2848     -- local f_image = formatters[ [[figure("%s") xysized (%N,%N) shifted (%N,%N)]] ]
2849        local f_image = formatters[ [[svgembeddedfigure(%i) xysized (%N,%N) shifted (%N,%N)]] ]
2850
2851     -- local nofimages = 0
2852
2853        function handlers.image(c)
2854            local at = c.at
2855            local im = rawget(at,"xlink:href")
2856            if im then
2857                local kind, data = match(im,"^data:image/([a-z]+);base64,(.*)$")
2858                if kind == "png" then
2859                    -- ok
2860                elseif kind == "jpeg" then
2861                    kind = "jpg"
2862                else
2863                    kind = false
2864                end
2865                if kind and data then
2866                    local w  = rawget(at,"width")
2867                    local h  = rawget(at,"height")
2868                    local x  = rawget(at,"x")
2869                    local y  = rawget(at,"y")
2870                    w = w and asnumber_x(w)
2871                    h = h and asnumber_y(h)
2872                    x = x and asnumber_vx(x) or 0
2873                    y = y and asnumber_vy(y) or 0
2874                    local data = basexx.decode64(data)
2875                 -- local name  = "temp-svg-image-" .. nofimages .. "." .. kind
2876                    local index = images.storedata("svg", {
2877                        kind = kind,
2878                        data = data,
2879                        info = graphics.identifiers[kind](data,"string"),
2880                    })
2881                 -- io.savedata(name,data)
2882                    if not w or not h then
2883                        if info then
2884                            -- todo: keep aspect ratio attribute
2885                            local xsize = info.xsize
2886                            local ysize = info.ysize
2887                            if not w then
2888                                if not h then
2889                                    w = xsize
2890                                    h = ysize
2891                                else
2892                                    w = (h / ysize) * xsize
2893                                end
2894                            else
2895                                h = (w / xsize) * ysize
2896                            end
2897                        end
2898                    end
2899                    -- safeguard:
2900                    if not w then w = h or 1 end
2901                    if not h then h = w or 1 end
2902                 -- luatex.registertempfile(name)
2903                 -- flushobject(f_image(name,w,h,x,y - h),at)
2904                    flushobject(f_image(index,w,h,x,y - h),at)
2905                else
2906                    -- nothing done
2907                end
2908            end
2909        end
2910
2911    end
2912
2913    -- these transform: g a text svg symbol
2914
2915    do
2916
2917        function handlers.a(c)
2918            process(c,"/*")
2919        end
2920
2921        function handlers.g(c) -- much like flushobject so better split and share
2922            local at = c.at
2923
2924            local btransform, etransform, transform = handletransform(at)
2925            local cpath, clippath, ctransform = handleclippath(at)
2926            local bopacity, copacity, eopacity = sharedopacity(at)
2927            if copacity then
2928                r = r + 1 ; result[r] = bopacity
2929            end
2930
2931            if cpath then
2932                r = r + 1 ; result[r] = s_clip_start
2933            end
2934
2935            if btransform then
2936                r = r + 1 result[r] = btransform
2937            end
2938            local _transform = transform
2939            local _clippath  = clippath
2940            at["transform"] = false
2941            at["clip-path"] = false
2942
2943            process(c,"/!(defs|symbol)") -- /*
2944
2945            at["transform"] = _transform
2946            at["clip-path"] = _clippath
2947
2948            if etransform then -- maybe move after cpath
2949                r = r + 1 ; result[r] = etransform
2950            end
2951            if cpath then
2952                local f_done = cpath.evenodd
2953                if cpath.curve then
2954                    f_done = f_done and f_eoclip_stop_c or f_clip_stop_c
2955                else
2956                    f_done = f_done and f_eoclip_stop_l or f_clip_stop_l
2957                end
2958                r = r + 1 ; result[r] = f_done(cpath.path,ctransform or "")
2959            end
2960            if copacity then
2961                r = r + 1 ; result[r] = copacity
2962                r = r + 1 ; result[r] = eopacity
2963            end
2964        end
2965
2966        -- this will never really work out
2967        --
2968        -- todo: register text in lua in mapping with id, then draw mapping unless overloaded
2969        --       using lmt_svglabel with family,style,weight,size,id passed
2970
2971        -- nested tspans are messy: they can have displacements but in inkscape we also
2972        -- see x and y (inner and outer element)
2973
2974        -- The size is a bit of an issue. I assume that the specified size relates to the
2975        -- designsize but we want to be able to use other fonts.
2976
2977        -- a mix of text and spans and possibly wrap (where xy is to be ignored) ... bah ...
2978        -- it's fuzzy when we have a span with positions mixed with text ... basically that
2979        -- is a box and we can assume that an editor then has all positioned
2980
2981        do
2982
2983            local s_start     <const> = "\\svgstart "
2984            local s_stop      <const> = "\\svgstop "
2985            local f_set               = formatters["\\svgset{%N}{%N}"] -- we need a period
2986            local f_color_c           = formatters["\\svgcolorc{%.3N}{%.3N}{%.3N}{"]
2987            local f_color_o           = formatters["\\svgcoloro{%.3N}{"]
2988            local f_color_b           = formatters["\\svgcolorb{%.3N}{%.3N}{%.3N}{%.3N}{"]
2989            local f_poscode           = formatters["\\svgpcode{%N}{%N}{%s}"]
2990            local f_poschar           = formatters["\\svgpchar{%N}{%N}{%s}"]
2991            local f_posspace          = formatters["\\svgpspace{%N}{%N}"]
2992            local f_code              = formatters["\\svgcode{%s}"]
2993            local f_char              = formatters["\\svgchar{%s}"]
2994            local s_space     <const> = "\\svgspace "
2995            local f_size              = formatters["\\svgsize{%0.6f}"]             -- we need a period
2996            local f_font              = formatters["\\svgfont{%s}{%s}{%s}"]
2997            local f_hashed            = formatters["\\svghashed{%s}"]
2998
2999            ----- p_texescape = lpegpatterns.texescape
3000
3001            local anchors = {
3002                ["start"]  = "drt",
3003                ["end"]    = "dlft",
3004                ["middle"] = "d",
3005            }
3006
3007            -- we can now just use the lmt maptext feature
3008
3009            local f_text_normal_svg   = formatters['(onetimetextext.%s("%s") shifted (%N,%N))']
3010            local f_text_simple_svg   = formatters['onetimetextext.%s("%s")']
3011            local f_mapped_normal_svg = formatters['(svgtext("%s") shifted (%N,%N))']
3012            local f_mapped_simple_svg = formatters['svgtext("%s")']
3013
3014            local cssfamily  = css.family
3015            local cssstyle   = css.style
3016            local cssweight  = css.weight
3017            local csssize    = css.size
3018
3019            local usedfonts  = setmetatableindex(function(t,k)
3020                local v = setmetatableindex("table")
3021                t[k] = v
3022                return v
3023            end)
3024
3025            -- For now as I need it for my (some 1500) test files.
3026
3027            local function checkedfamily(name)
3028                if find(name,"^.-verdana.-$") then
3029                    name = "verdana"
3030                end
3031                return name
3032            end
3033
3034            -- todo: only escape some chars and handle space
3035
3036         -- An arbitrary mix of text and spans with x/y is asking for troubles. The fact that the
3037         -- description in the (proposed) standard is so complex indicates this (its also looks
3038         -- like reveng application specs and doesn't aim at simplicity. Basically we have two
3039         -- cases: positioned lines and words and such (text & span with xy), or just stripes of
3040         -- text and span. Free flow automatically broken into lines text is kind of strange in
3041         -- svg and the fact that glyph placement is dropped is both an indication that svg lost
3042         -- part of its purpose and probably also that it never really was a standard (although
3043         -- maybe today standards are just short term specifications. Who knows.
3044
3045         -- text with spans, all with x/y
3046         -- text mixed with spans, no xy in inner elements
3047         --
3048         -- the spec says that nested x/y are absolute
3049
3050            local defaultsize = 10
3051
3052            local sensitive = { -- todo: characters.sensitive
3053                ["#"] = true,
3054                ["$"] = true,
3055                ["%"] = true,
3056                ["&"] = true,
3057               ["\\"] = true,
3058                ["{"] = true,
3059                ["|"] = true,
3060                ["}"] = true,
3061                ["~"] = true,
3062            }
3063
3064            -- messy: in nested spans (they happen) the x/y are not accumulated
3065
3066            local function validdelta(usedscale,d)
3067                if d then
3068                    local value, unit = match(d,"^([%A]-)(%a+)")
3069                    value = tonumber(value) or 0
3070                    if not unit then
3071                        return value .. "bp"
3072                    elseif unit == "ex" or unit == "em" then
3073                        return (usedscale * value) .. unit
3074                    else
3075                        return value .. "bp"
3076                    end
3077                else
3078                    return "0bp"
3079                end
3080            end
3081
3082            local cleanfontname = fonts.names.cleanname
3083
3084            local x_family = false
3085            local x_weight = false
3086            local x_style  = false
3087
3088            local function collect(parent,t,c,x,y,size,scale,family,tx,ty,tdx,tdy)
3089                if c.special then
3090                    return nil
3091                end
3092                local dt           = c.dt
3093                local nt           = #dt
3094                local at           = c.at
3095                local tg           = c.tg
3096                local ax           = rawget(at,"x")
3097                local ay           = rawget(at,"y")
3098                local v_opacity    = tonumber(at["fill-opacity"])
3099                local v_fill       = at["fill"]
3100                local v_family     = at["font-family"]
3101                local v_style      = at["font-style"]
3102                local v_weight     = at["font-weight"]
3103                local v_size       = at["font-size"]
3104                local v_lineheight = at["line-height"]
3105                --
3106                ax = ax and asnumber_vx(ax) or x
3107                ay = ay and asnumber_vy(ay) or y
3108                --
3109                if v_family then v_family = cssfamily(v_family) end
3110                if v_style  then v_style  = cssstyle (v_style)  end
3111                if v_weight then v_weight = cssweight(v_weight) end
3112                if v_size   then v_size   = csssize  (v_size,factors,size/100) or tonumber(v_size) end
3113                --
3114                if not v_family then v_family = family   end
3115                if not v_weight then v_weight = "normal" end
3116                if not v_style  then v_style  = "normal" end
3117                --
3118                if v_family then
3119                    v_family = cleanfontname(v_family)
3120                    v_family = checkedfamily(v_family)
3121                end
3122                --
3123                usedfonts[v_family][v_weight][v_style] = true
3124                --
3125                local lh = v_lineheight and asnumber_vx(v_lineheight) or false
3126                --
3127                ax = ax - x
3128                ay = ay - y
3129                --
3130                local usedsize  = v_size or defaultsize
3131                local usedscale = usedsize / defaultsize
3132                --
3133                -- todo: rotate            : list of numbers
3134                -- todo: lengthAdjust      : spacing|spacingAndGlyphs
3135                -- todo: textLength        : scale to width
3136                -- toto: font-size-adjust
3137                -- toto: font-stretch
3138                -- letter-spacing
3139                -- word-spacing
3140                -- writing-mode:lr-tb
3141                --
3142                local newfont = v_family ~= x_family or v_weight ~= x_weight or v_style ~= x_style
3143                if newfont then
3144                    x_family = v_family
3145                    x_weight = v_weight
3146                    x_style  = v_style
3147                    t[#t+1] = f_font(v_family,v_weight,v_style)
3148                    t[#t+1] = "{"
3149                end
3150                t[#t+1] = f_size(usedscale)
3151                t[#t+1] = "{"
3152                --
3153                if trace_fonts then
3154                    -- we can hash and keep it when no change
3155                    report("element        : %s",c.tg)
3156                    report("  font family  : %s",v_family)
3157                    report("  font weight  : %s",v_weight)
3158                    report("  font style   : %s",v_style)
3159                    report("  parent size  : %s",size)
3160                 -- report("  parent scale : %s",scale)
3161                    report("  used size    : %s",v_size or defaultsize)
3162                end
3163                --
3164                local ecolored = v_fill    ~= ""             and v_fill    or false
3165                local opacity  = v_opacity ~= ignoredopacity and v_opacity or false
3166                --
3167                -- todo cmyk
3168                --
3169                if ecolored then
3170                    local r, g, b = colorcomponents(v_fill)
3171                    if r and g and b then
3172                        if opacity then
3173                            t[#t+1] = f_color_b(r,g,b,opacity)
3174                        else
3175                            t[#t+1] = f_color_c(r,g,b)
3176                        end
3177                    elseif opacity then
3178                        t[#t+1] = f_color_o(opacity)
3179                    else
3180                        ecolored = false
3181                    end
3182                elseif opacity then
3183                    t[#t+1] = f_color_o(opacity)
3184                end
3185                --
3186                local hasa = ax ~= 0 or ay ~= 0
3187                if hasa then
3188                    -- we abuse the fact that flushing layers can be nested
3189                    t[#t+1] = f_set(ax or 0,ay or 0)
3190                    t[#t+1] = "{"
3191                end
3192                for i=1,nt do
3193                    local di = dt[i]
3194                    if type(di) == "table" then
3195                        -- when x or y then absolute else inline
3196                        if #di.dt > 0 then
3197                            collect(tg,t,di,x,y,usedsize,usedscale,v_family)
3198                        end
3199                    else
3200                        -- check for preserve
3201                        if i == 1 then
3202                            di = gsub(di,"^%s+","")
3203                        end
3204                        if i == nt then
3205                            di = gsub(di,"%s+$","")
3206                        end
3207                        local chars = utfsplit(di)
3208                        if svghash then
3209                            -- dx dy
3210                            di = f_hashed(svghash[di])
3211                        else
3212                            if tx or ty or tdx or tdy then
3213                                local txi, tyi, tdxi, tdyi
3214                                for i=1,#chars do
3215                                    txi  = tx  and (tx [i] or txi )
3216                                    tyi  = ty  and (ty [i] or tyi )
3217                                    tdxi = tdx and (tdx[i] or tdxi) or 0
3218                                    tdyi = tdy and (tdy[i] or tdyi) or 0
3219                                    local dx = (txi and (txi - x) or 0) + tdxi
3220                                    local dy = (tyi and (tyi - y) or 0) + tdyi
3221                                    local ci = chars[i]
3222                                    if ci == " " then
3223                                        chars[i] = f_posspace(dx, dy)
3224                                    elseif sensitive[ci] then
3225                                        chars[i] = f_poscode(dx, dy, utfbyte(ci))
3226                                    else
3227                                        chars[i] = f_poschar(dx, dy, ci)
3228                                    end
3229                                end
3230                                di = "{" .. concat(chars) .. "}"
3231                                t[#t+1] = di
3232                            else
3233                                -- this needs to be texescaped ! and even quotes and newlines
3234                                -- or we could register it but that's a bit tricky as we nest
3235                                -- and don't know what we can expect here
3236                             -- di = lpegmatch(p_texescape,di) or di
3237                                for i=1,#chars do
3238                                    local ci = chars[i]
3239                                    if ci == " " then
3240                                        chars[i] = s_space
3241                                    elseif sensitive[ci] then
3242                                        chars[i] = f_code(utfbyte(ci))
3243                                    else
3244                                        chars[i] = f_char(ci)
3245                                     -- chars[i] = ci
3246                                    end
3247                                end
3248                                di = concat(chars)
3249                                t[#t+1] = di
3250                            end
3251                        end
3252                    end
3253                end
3254                if hasa then
3255                    if t[#t] == "{" then
3256                        t[#t] = nil
3257                        t[#t] = nil
3258                    else
3259                        t[#t+1] = "}"
3260                    end
3261                end
3262                --
3263                if opacity or ecolored then
3264                    t[#t+1] = "}"
3265                end
3266                --
3267                t[#t+1] = "}"
3268                --
3269                if newfont then
3270                    t[#t+1] = "}"
3271                end
3272                --
3273                return t
3274            end
3275
3276            -- case 1: just text, maybe with spans
3277            -- case 2: only positioned spans
3278            -- case 3: just text, seen as label
3279
3280            local textlevel = 0
3281
3282            function handlers.text(c)
3283                if textlevel == 0 then
3284                    x_family = v_family
3285                    x_weight = v_weight
3286                    x_style  = v_style
3287                end
3288                --
3289                textlevel = textlevel + 1
3290                -- analyze
3291                local only = fullstrip(xmltextonly(c))
3292                local at   = c.at
3293                local x    = rawget(at,"x")
3294                local y    = rawget(at,"y")
3295
3296                local dx   = rawget(at,"dx")
3297                local dy   = rawget(at,"dy")
3298
3299                local tx   = asnumber_vx_t(x)
3300                local ty   = asnumber_vy_t(y)
3301
3302                local tdx  = asnumber_vx_t(dx)
3303                local tdy  = asnumber_vy_t(dy)
3304
3305                x  = tx[1]  or 0 -- catch bad x/y spec
3306                y  = ty[1]  or 0 -- catch bad x/y spec
3307
3308                dx = tdx[1] or 0 -- catch bad x/y spec
3309                dy = tdy[1] or 0 -- catch bad x/y spec
3310
3311                local v_fill = at["fill"]
3312                if not v_fill or v_fill == "none" then
3313                    v_fill = "black"
3314                end
3315                local color, opacs, transform, opacity, option = fillproperties(v_fill,at)
3316                local anchor = anchors[at["text-anchor"] or "start"] or "drt"
3317                local remap = metapost.remappedtext(only)
3318                -- x = x + dx
3319                -- y = y + dy
3320                if remap then
3321                    if x == 0 and y == 0 then
3322                        only = f_mapped_simple_svg(remap.index)
3323                    else
3324                        only = f_mapped_normal_svg(remap.index,x,y)
3325                    end
3326                    flushobject(only,at,color,opacity)
3327                    if trace_text then
3328                        report("text: %s",only)
3329                    end
3330                elseif option == "invisible" then
3331                    if trace_text then
3332                        report("invisible text: %s",only)
3333                    end
3334                else
3335                    local scale  = 1
3336                    local textid = 0
3337                    local result = { }
3338                    local nx     = #tx
3339                    local ny     = #ty
3340                    local ndx    = #tdx
3341                    local ndy    = #tdy
3342                    --
3343                    local t = { }
3344                    t[#t+1] = s_start
3345                    if nx > 1 or ny > 1 or ndx > 1 or ndy > 1 then
3346                        collect(tg,t,c,x,y,defaultsize,1,"serif",tx,ty,tdx,tdy)
3347                    else
3348                        collect(tg,t,c,x,y,defaultsize,1,"serif")
3349                    end
3350                    t[#t+1] = s_stop
3351                    t = concat(t)
3352                    if x == 0 and y == 0 then
3353                        t = f_text_simple_svg(anchor,t)
3354                    else -- dx dy
3355                        t = f_text_normal_svg(anchor,t,x,y)
3356                    end
3357                 -- flushobject(t,at,color,opacity) -- otherwise mixup with transparency
3358                    flushobject(t,at,false,false)
3359                    if trace_text then
3360                        report("text: %s",result)
3361                    end
3362                end
3363                --
3364                textlevel = textlevel - 1
3365            end
3366
3367            function metapost.reportsvgfonts()
3368                for family, weights in sortedhash(usedfonts) do
3369                    for weight, styles in sortedhash(weights) do
3370                        for style in sortedhash(styles) do
3371                            report("used font: %s-%s-%s",family,weight,style)
3372                        end
3373                    end
3374                end
3375            end
3376
3377            statistics.register("used svg fonts",function()
3378                if next(usedfonts) then
3379                    -- also in log file
3380                    logs.startfilelogging(report,"used svg fonts")
3381                    local t = { }
3382                    for family, weights in sortedhash(usedfonts) do
3383                        for weight, styles in sortedhash(weights) do
3384                            for style in sortedhash(styles) do
3385                                report("%s-%s-%s",family,weight,style)
3386                                t[#t+1] = formatters["%s-%s-%s"](family,weight,style)
3387                            end
3388                        end
3389                    end
3390                    logs.stopfilelogging()
3391                    return concat(t," ")
3392                end
3393            end)
3394
3395        end
3396
3397        function handlers.svg(c,x,y,w,h,noclip,notransform,normalize)
3398            local at = c.at
3399
3400            local wrapupviewport
3401            local bhacked
3402            local ehacked
3403            local wd = w
3404         -- local ex, em
3405            local xpct, ypct, rpct
3406
3407            local btransform, etransform, transform = handletransform(at)
3408
3409            if trace then
3410                report("view: %s, xpct %N, ypct %N","before",percentage_x,percentage_y)
3411            end
3412
3413            local viewbox = at.viewBox
3414
3415            if viewbox then
3416                x, y, w, h = handleviewbox(viewbox)
3417                if trace then
3418                    report("viewbox: x %N, y %N, width %N, height %N",x,y,w,h)
3419                end
3420            end
3421            if not w or not h or w == 0 or h == 0 then
3422                noclip = true
3423            end
3424            if h then
3425                --
3426             -- em = factors["em"]
3427             -- ex = factors["ex"]
3428             -- factors["em"] = em
3429             -- factors["ex"] = ex
3430                --
3431                xpct = percentage_x
3432                ypct = percentage_y
3433                rpct = percentage_r
3434                percentage_x = w / 100
3435                percentage_y = h / 100
3436                percentage_r = (sqrt(w^2 + h^2) / sqrt(2)) / 100
3437                if trace then
3438                    report("view: %s, xpct %N, ypct %N","inside",percentage_x,percentage_y)
3439                end
3440                wrapupviewport = viewport(x,y,w,h,noclip)
3441            end
3442            -- todo: combine transform and offset here
3443
3444            -- some fonts need this (bad transforms + viewbox)
3445            if v and normalize and w and wd and w ~= wd and w > 0 and wd > 0 then
3446                bhacked = s_wrapped_start
3447                ehacked = f_wrapped_stop(y or 0,wd/w)
3448            end
3449            if btransform then
3450                r = r + 1 ; result[r] = btransform
3451            end
3452            if bhacked then
3453                r = r + 1 ; result[r] = bhacked
3454            end
3455            local boffset, eoffset = handleoffset(at)
3456            if boffset then
3457                r = r + 1 result[r] = boffset
3458            end
3459
3460            at["transform"] = false
3461            at["viewBox"]   = false
3462
3463            process(c,"/!(defs|symbol)")
3464
3465            at["transform"] = transform
3466            at["viewBox"]   = viewbox
3467
3468            if eoffset then
3469                r = r + 1 result[r] = eoffset
3470            end
3471            if ehacked then
3472                r = r + 1 ; result[r] = ehacked
3473            end
3474            if etransform then
3475                r = r + 1 ; result[r] = etransform
3476            end
3477            if h then
3478                --
3479             -- factors["em"] = em
3480             -- factors["ex"] = ex
3481                --
3482                percentage_x = xpct
3483                percentage_y = ypct
3484                percentage_r = rpct
3485                if wrapupviewport then
3486                    wrapupviewport()
3487                end
3488            end
3489            if trace then
3490                report("view: %s, xpct %N, ypct %N","after",percentage_x,percentage_y)
3491            end
3492        end
3493
3494    end
3495
3496    process = function(x,p)
3497        for c in xmlcollected(x,p) do
3498            local tg = c.tg
3499            local h  = handlers[c.tg]
3500            if h then
3501                h(c)
3502            end
3503        end
3504    end
3505
3506    -- For huge inefficient files there can be lots of garbage to collect so
3507    -- maybe we should run the collector when a file is larger than say 50K.
3508
3509    function metapost.svgtomp(specification,pattern,notransform,normalize)
3510        local mps = ""
3511        local svg = specification.data
3512        images.resetstore("svg")
3513        if type(svg) == "string" then
3514            svg = xmlconvert(svg)
3515        end
3516        if svg then
3517            local c = xmlfirst(svg,pattern or "/svg")
3518            if c then
3519                root        = svg
3520                result      = { }
3521                r           = 0
3522                definitions = { }
3523                tagstyles   = { }
3524                classstyles = { }
3525                colormap    = specification.colormap
3526                usedcolors  = trace_colors and setmetatableindex("number") or false
3527                for s in xmlcollected(c,"style") do -- can also be in a def, so let's play safe
3528                    handlestyle(c)
3529                end
3530                handlechains(c)
3531                xmlinheritattributes(c) -- put this in handlechains
3532                handledefinitions(c)
3533                handlers.svg (
3534                    c,
3535                    specification.x,
3536                    specification.y,
3537                    specification.width,
3538                    specification.height,
3539                    specification.noclip,
3540                    notransform,
3541                    normalize,
3542                    specification.remap
3543                )
3544                if trace_result == "file" then
3545                    io.savedata(
3546                        tex.jobname .. "-svg-to-mp.tex",
3547                        "\\startMPpage[instance=doublefun]\n" .. concat(result,"\n") .. "\n\\stopMPpage\n"
3548                    )
3549                elseif trace_result then
3550                    report("result graphic:\n    %\n    t",result)
3551                end
3552                if usedcolors and next(usedcolors) then
3553                    report("graphic %a uses colors: %s",specification.id or "unknown",table.sequenced(usedcolors))
3554                end
3555                mps         = concat(result," ")
3556                root        = false
3557                result      = false
3558                r           = false
3559                definitions = false
3560                tagstyles   = false
3561                classstyles = false
3562                colormap    = false
3563            else
3564                report("missing svg root element")
3565            end
3566        else
3567            report("bad svg blob")
3568        end
3569        return mps
3570    end
3571
3572end
3573
3574-- These helpers might move to their own module .. some day ... also they will become
3575-- a bit more efficient, because we now go to mp and back which is kind of redundant,
3576-- but for now it will do.
3577
3578do
3579
3580    local bpfactor <const> = number.dimenfactors.bp
3581
3582    function metapost.includesvgfile(filename,offset) -- offset in sp
3583        local fullname = resolvers.findbinfile(filename)
3584        if lfs.isfile(fullname) then
3585            context.startMPcode("doublefun")
3586                context('draw lmt_svg [ filename = "%s", offset = %N ] ;',filename,(offset or 0)*bpfactor)
3587            context.stopMPcode()
3588        end
3589    end
3590
3591    function metapost.includesvgbuffer(name,offset) -- offset in sp
3592        context.startMPcode("doublefun")
3593            context('draw lmt_svg [ buffer = "%s", offset = %N ] ;',name or "",(offset or 0)*bpfactor)
3594        context.stopMPcode()
3595    end
3596
3597    interfaces.implement {
3598        name      = "includesvgfile",
3599        actions   = metapost.includesvgfile,
3600        arguments = { "string", "dimension" },
3601    }
3602
3603    interfaces.implement {
3604        name      = "includesvgbuffer",
3605        actions   = metapost.includesvgbuffer,
3606        arguments = { "string", "dimension" },
3607    }
3608
3609    function metapost.showsvgpage(data)
3610        local dd = data.data
3611        if not dd then
3612            local filename = data.filename
3613            local fullname = filename and resolvers.findbinfile(filename)
3614            dd = fullname and table.load(fullname)
3615        end
3616        if type(dd) == "table" then
3617            local comment = data.comment
3618            local offset  = data.pageoffset
3619            local index   = data.index
3620            local first   = math.max(index or 1,1)
3621            local last    = math.min(index or #dd,#dd)
3622            for i=first,last do
3623                local d = setmetatableindex( {
3624                    data       = dd[i],
3625                    comment    = comment and i or false,
3626                    pageoffset = offset or nil,
3627                }, data)
3628                metapost.showsvgpage(d)
3629            end
3630        elseif data.method == "code" then
3631            context.startMPcode(doublefun)
3632                context(metapost.svgtomp(data))
3633            context.stopMPcode()
3634        else
3635            context.startMPpage { instance = "doublefun", offset = data.pageoffset or nil }
3636                context(metapost.svgtomp(data))
3637                local comment = data.comment
3638                if comment then
3639                    context("draw boundingbox currentpicture withcolor .6red ;")
3640                    context('draw textext.bot("\\strut\\tttf %s") ysized (10pt) shifted center bottomboundary currentpicture ;',comment)
3641                end
3642            context.stopMPpage()
3643        end
3644    end
3645
3646    function metapost.typesvgpage(data)
3647        local dd = data.data
3648        if not dd then
3649            local filename = data.filename
3650            local fullname = filename and resolvers.findbinfile(filename)
3651            dd = fullname and table.load(fullname)
3652        end
3653        if type(dd) == "table" then
3654            local index = data.index
3655            if index and index > 0 and index <= #dd then
3656                data = dd[index]
3657            else
3658                data = nil
3659            end
3660        end
3661        if type(data) == "string" and data ~= "" then
3662            buffers.assign("svgpage",data)
3663            context.typebuffer ({ "svgpage" }, { option = "XML", strip = "yes" })
3664        end
3665    end
3666
3667    function metapost.svgtopdf(data,...)
3668        local mps = metapost.svgtomp(data,...)
3669        if mps then
3670            -- todo: special instance, only basics needed
3671            local pdf = metapost.simple("metafun",mps,true,false,"svg")
3672            if pdf then
3673                return pdf
3674            else
3675                -- message
3676            end
3677        else
3678            -- message
3679        end
3680    end
3681
3682end
3683
3684do
3685
3686    local runner = sandbox.registerrunner {
3687        name     = "otfsvg2pdf",
3688        program  = "context",
3689        template = "--batchmode --purgeall --runs=2 %filename%",
3690        reporter = report_svg,
3691    }
3692
3693    -- By using an independent pdf file instead of pdf streams we can use resources and still
3694    -- cache. This is the old method updated. Maybe a future version will just do this runtime
3695    -- but for now this is the most efficient method.
3696
3697    local decompress = gzip.decompress
3698    local compress   = gzip.compress
3699
3700    function metapost.svgshapestopdf(svgshapes,pdftarget,report_svg)
3701        local texname   = "temp-otf-svg-to-pdf.tex"
3702        local pdfname   = "temp-otf-svg-to-pdf.pdf"
3703        local tucname   = "temp-otf-svg-to-pdf.tuc"
3704        local nofshapes = #svgshapes
3705        local pdfpages  = { filename = pdftarget }
3706        local pdfpage   = 0
3707        local t         = { }
3708        local n         = 0
3709        --
3710        os.remove(texname)
3711        os.remove(pdfname)
3712        os.remove(tucname)
3713        --
3714        if report_svg then
3715            report_svg("processing %i svg containers",nofshapes)
3716            statistics.starttiming(pdfpages)
3717        end
3718        --
3719        -- can be option:
3720        --
3721     -- n = n + 1 ; t[n] = "\\nopdfcompression"
3722        --
3723        n = n + 1 ; t[n] = "\\starttext"
3724        n = n + 1 ; t[n] = "\\setupMPpage[alternative=offset,instance=doublefun]"
3725        --
3726        for i=1,nofshapes do
3727            local entry = svgshapes[i]
3728            local data  = entry.data
3729            if decompress then
3730                data = decompress(data) or data
3731            end
3732            local specification = {
3733                data   = xmlconvert(data),
3734                x      = 0,
3735                y      = 1000,
3736                width  = 1000,
3737                height = 1000,
3738                noclip = true,
3739            }
3740            for index=entry.first,entry.last do
3741                if not pdfpages[index] then
3742                    pdfpage = pdfpage + 1
3743                    pdfpages[index] = pdfpage
3744                    local pattern = "/svg[@id='glyph" .. index .. "']"
3745                    n = n + 1 ; t[n] = "\\startMPpage"
3746                    n = n + 1 ; t[n] = metapost.svgtomp(specification,pattern,true,true) or ""
3747                    n = n + 1 ; t[n] = "\\stopMPpage"
3748                end
3749            end
3750        end
3751        n = n + 1 ; t[n] = "\\stoptext"
3752        io.savedata(texname,concat(t,"\n"))
3753        runner { filename = texname }
3754        os.remove(pdftarget)
3755        file.copy(pdfname,pdftarget)
3756        if report_svg then
3757            statistics.stoptiming(pdfpages)
3758            report_svg("svg conversion time %s",statistics.elapsedseconds(pdfpages))
3759        end
3760        os.remove(texname)
3761        os.remove(pdfname)
3762        os.remove(tucname)
3763        return pdfpages
3764    end
3765
3766    function metapost.svgshapestomp(svgshapes,report_svg)
3767        local nofshapes = #svgshapes
3768        local mpshapes = { }
3769        if report_svg then
3770            report_svg("processing %i svg containers",nofshapes)
3771            statistics.starttiming(mpshapes)
3772        end
3773        for i=1,nofshapes do
3774            local entry = svgshapes[i]
3775            local data  = entry.data
3776            if decompress then
3777                data = decompress(data) or data
3778            end
3779            local specification = {
3780                data   = xmlconvert(data),
3781                x      = 0,
3782                y      = 1000,
3783                width  = 1000,
3784                height = 1000,
3785                noclip = true,
3786            }
3787            for index=entry.first,entry.last do
3788                if not mpshapes[index] then
3789                    local pattern = "/svg[@id='glyph" .. index .. "']"
3790                    local mpcode  = metapost.svgtomp(specification,pattern,true,true) or ""
3791                    if mpcode ~= "" and compress then
3792                        mpcode = compress(mpcode) or mpcode
3793                    end
3794                    mpshapes[index] = mpcode
3795                end
3796            end
3797        end
3798        if report_svg then
3799            statistics.stoptiming(mpshapes)
3800            report_svg("svg conversion time %s",statistics.elapsedseconds(mpshapes))
3801        end
3802        return mpshapes
3803    end
3804
3805    function metapost.svgglyphtomp(fontname,unicode)
3806        if fontname and unicode then
3807            local id = fonts.definers.internal { name = fontname }
3808            if id then
3809                local tfmdata = fonts.hashes.identifiers[id]
3810                if tfmdata then
3811                    local properties = tfmdata.properties
3812                    local svg        = properties.svg
3813                    local hash       = svg and svg.hash
3814                    local timestamp  = svg and svg.timestamp
3815                    if hash then
3816                        local svgfile   = containers.read(fonts.handlers.otf.svgcache,hash)
3817                        local svgshapes = svgfile and svgfile.svgshapes
3818                        if svgshapes then
3819                            if type(unicode) == "string" then
3820                                unicode = utfbyte(unicode)
3821                            end
3822                            local chardata = tfmdata.characters[unicode]
3823                            local index    = chardata and chardata.index
3824                            if index then
3825                                for i=1,#svgshapes do
3826                                    local entry = svgshapes[i]
3827                                    if index >= entry.first and index <= entry.last then
3828                                        local data  = entry.data
3829                                        if data then
3830                                            local root = xml.convert(gzip.decompress(data) or data)
3831                                            return metapost.svgtomp (
3832                                                {
3833                                                    data   = root,
3834                                                    x      = 0,
3835                                                    y      = 1000,
3836                                                    width  = 1000,
3837                                                    height = 1000,
3838                                                    noclip = true,
3839                                                },
3840                                                "/svg[@id='glyph" .. index .. "']",
3841                                                true,
3842                                                true
3843                                            )
3844                                        end
3845                                    end
3846                                end
3847                            end
3848                        end
3849                    end
3850                end
3851            end
3852        end
3853    end
3854
3855end
3856