font-dsp.lmt /size: 188 Kb    last modification: 2025-02-21 11:03
1if not modules then modules = { } end modules ['font-dsp'] = {
2    version   = 1.001,
3    optimize  = true,
4    comment   = "companion to font-ini.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-- many 0,0 entry/exit
11
12-- This loader went through a few iterations. First I made a ff compatible one so
13-- that we could do some basic checking. Also some verbosity was added (named
14-- glyphs). Eventually all that was dropped for a context friendly format, simply
15-- because keeping the different table models in sync too to much time. I have the
16-- old file somewhere. A positive side effect is that we get an (upto) much smaller
17-- smaller tma/tmc file. In the end the loader will be not much slower than the
18-- c based ff one.
19
20-- Being binary encoded, an opentype is rather compact. When expanded into a Lua table
21-- quite some memory can be used. This is very noticeable in the ff loader, which for
22-- a good reason uses a verbose format. However, when we use that data we create a couple
23-- of hashes. In the Lua loader we create these hashes directly, which save quite some
24-- memory.
25--
26-- We convert a font file only once and then cache it. Before creating the cached instance
27-- packing takes place: common tables get shared. After (re)loading and unpacking we then
28-- get a rather efficient internal representation of the font. In the new loader there is a
29-- pitfall. Because we use some common coverage magic we put a bit more information in
30-- the mark and cursive coverage tables than strickly needed: a reference to the coverage
31-- itself. This permits a fast lookup of the second glyph involved. In the marks we
32-- expand the class indicator to a class hash, in the cursive we use a placeholder that gets
33-- a self reference. This means that we cannot pack these subtables unless we add a unique
34-- id per entry (the same one per coverage) and that makes the tables larger. Because only a
35-- few fonts benefit from this, I decided to not do this. Experiments demonstrated that it
36-- only gives a few percent gain (on for instance husayni we can go from 845K to 828K
37-- bytecode). Better stay conceptually clean than messy compact.
38
39-- When we can reduce all basic lookups to one step we might safe a bit in the processing
40-- so then only chains are multiple.
41
42-- I used to flatten kerns here but that has been moved elsewhere because it polutes the code
43-- here and can be done fast afterwards. One can even wonder if it makes sense to do it as we
44-- pack anyway. In a similar fashion the unique placeholders in anchors in marks have been
45-- removed because packing doesn't save much there anyway.
46
47-- Although we have a bit more efficient tables in the cached files, the internals are still
48-- pretty similar. And although we have a slightly more direct coverage access the processing
49-- of node lists is not noticeable faster for latin texts, but for arabic we gain some 10%
50-- (and could probably gain a bit more).
51
52-- All this packing in the otf format is somewhat obsessive as nowadays 4K resolution
53-- multi-gig videos pass through our networks and storage and memory is abundant.
54
55-- Although we use a few table readers there i sno real gain in there (apart from having
56-- less code. After all there are often not that many demanding features.
57
58local next, type, tonumber = next, type, tonumber
59local gsub = string.gsub
60local lower = string.lower
61local sub = string.sub
62local strip = string.strip
63local tohash = table.tohash
64local concat = table.concat
65local copy = table.copy
66local reversed = table.reversed
67local sort = table.sort
68local insert = table.insert
69local round = math.round
70
71local settings_to_hash  = utilities.parsers.settings_to_hash_colon_too
72local setmetatableindex = table.setmetatableindex
73local formatters        = string.formatters
74local sortedkeys        = table.sortedkeys
75local sortedhash        = table.sortedhash
76local sequenced         = table.sequenced
77
78local report            = logs.reporter("otf reader")
79
80local readers           = fonts.handlers.otf.readers
81local streamreader      = readers.streamreader
82
83local setposition       = streamreader.setposition
84local getposition       = streamreader.getposition
85local readuinteger      = streamreader.readcardinal1
86local readushort        = streamreader.readcardinal2
87local readuoffset       = streamreader.readcardinal3
88local readulong         = streamreader.readcardinal4
89local readinteger       = streamreader.readinteger1
90local readshort         = streamreader.readinteger2
91local readstring        = streamreader.readstring
92local readtag           = streamreader.readtag
93local readbytes         = streamreader.readbytes
94local readfixed         = streamreader.readfixed4
95local read2dot14        = streamreader.read2dot14
96local skipshort         = streamreader.skipshort
97local skipbytes         = streamreader.skip
98local readbytetable     = streamreader.readbytetable
99local readbyte          = streamreader.readbyte
100local readcardinaltable = streamreader.readcardinaltable
101local readintegertable  = streamreader.readintegertable
102local readfword         = readshort
103
104local short   <const> = 2
105local ushort  <const> = 2
106local uoffset <const> = 3
107local ulong   <const> = 4
108
109directives.register("fonts.streamreader",function()
110
111    streamreader      = utilities.streams
112
113    setposition       = streamreader.setposition
114    getposition       = streamreader.getposition
115    readuinteger      = streamreader.readcardinal1
116    readushort        = streamreader.readcardinal2
117    readuoffset       = streamreader.readcardinal3
118    readulong         = streamreader.readcardinal4
119    readinteger       = streamreader.readinteger1
120    readshort         = streamreader.readinteger2
121    readstring        = streamreader.readstring
122    readtag           = streamreader.readtag
123    readbytes         = streamreader.readbytes
124    readfixed         = streamreader.readfixed4
125    read2dot14        = streamreader.read2dot14
126    skipshort         = streamreader.skipshort
127    skipbytes         = streamreader.skip
128    readbytetable     = streamreader.readbytetable
129    readbyte          = streamreader.readbyte
130    readcardinaltable = streamreader.readcardinaltable
131    readintegertable  = streamreader.readintegertable
132    readfword         = readshort
133
134end)
135
136local gsubhandlers      = { }
137local gposhandlers      = { }
138
139readers.gsubhandlers    = gsubhandlers
140readers.gposhandlers    = gposhandlers
141
142local helpers           = readers.helpers
143local gotodatatable     = helpers.gotodatatable
144local setvariabledata   = helpers.setvariabledata
145
146local lookupidoffset    <const> = -1    -- will become 1 when we migrate (only -1 for comparing with old)
147
148local classes = {
149    "base",
150    "ligature",
151    "mark",
152    "component",
153}
154
155local gsubtypes = {
156    "single",
157    "multiple",
158    "alternate",
159    "ligature",
160    "context",
161    "chainedcontext",
162    "extension",
163    "reversechainedcontextsingle",
164}
165
166local gpostypes = {
167    "single",
168    "pair",
169    "cursive",
170    "marktobase",
171    "marktoligature",
172    "marktomark",
173    "context",
174    "chainedcontext",
175    "extension",
176}
177
178local chaindirections = {
179    context                     =  0,
180    chainedcontext              =  1,
181    reversechainedcontextsingle = -1,
182}
183
184local function setmetrics(data,where,tag,d)
185    local w = data[where]
186    if w then
187        local v = w[tag]
188        if v then
189            -- it looks like some fonts set the value and not the delta
190         -- report("adding %s to %s.%s value %s",d,where,tag,v)
191            w[tag] = v + d
192        end
193    end
194end
195
196local variabletags = {
197    hasc = function(data,d) setmetrics(data,"windowsmetrics","typoascender",d) end,
198    hdsc = function(data,d) setmetrics(data,"windowsmetrics","typodescender",d) end,
199    hlgp = function(data,d) setmetrics(data,"windowsmetrics","typolinegap",d) end,
200    hcla = function(data,d) setmetrics(data,"windowsmetrics","winascent",d) end,
201    hcld = function(data,d) setmetrics(data,"windowsmetrics","windescent",d) end,
202    vasc = function(data,d) setmetrics(data,"vhea not done","ascent",d) end,
203    vdsc = function(data,d) setmetrics(data,"vhea not done","descent",d) end,
204    vlgp = function(data,d) setmetrics(data,"vhea not done","linegap",d) end,
205    xhgt = function(data,d) setmetrics(data,"windowsmetrics","xheight",d) end,
206    cpht = function(data,d) setmetrics(data,"windowsmetrics","capheight",d) end,
207    sbxs = function(data,d) setmetrics(data,"windowsmetrics","subscriptxsize",d) end,
208    sbys = function(data,d) setmetrics(data,"windowsmetrics","subscriptysize",d) end,
209    sbxo = function(data,d) setmetrics(data,"windowsmetrics","subscriptxoffset",d) end,
210    sbyo = function(data,d) setmetrics(data,"windowsmetrics","subscriptyoffset",d) end,
211    spxs = function(data,d) setmetrics(data,"windowsmetrics","superscriptxsize",d) end,
212    spys = function(data,d) setmetrics(data,"windowsmetrics","superscriptysize",d) end,
213    spxo = function(data,d) setmetrics(data,"windowsmetrics","superscriptxoffset",d) end,
214    spyo = function(data,d) setmetrics(data,"windowsmetrics","superscriptyoffset",d) end,
215    strs = function(data,d) setmetrics(data,"windowsmetrics","strikeoutsize",d) end,
216    stro = function(data,d) setmetrics(data,"windowsmetrics","strikeoutpos",d) end,
217    unds = function(data,d) setmetrics(data,"postscript","underlineposition",d) end,
218    undo = function(data,d) setmetrics(data,"postscript","underlinethickness",d) end,
219}
220
221local read_cardinal = {
222    streamreader.readcardinal1,
223    streamreader.readcardinal2,
224    streamreader.readcardinal3,
225    streamreader.readcardinal4,
226}
227
228local read_integer = {
229    streamreader.readinteger1,
230    streamreader.readinteger2,
231    streamreader.readinteger3,
232    streamreader.readinteger4,
233}
234
235directives.register("fonts.streamreader",function()
236
237    read_cardinal = {
238        streamreader.readcardinal1,
239        streamreader.readcardinal2,
240        streamreader.readcardinal3,
241        streamreader.readcardinal4,
242    }
243
244    read_integer = {
245        streamreader.readinteger1,
246        streamreader.readinteger2,
247        streamreader.readinteger3,
248        streamreader.readinteger4,
249    }
250
251end)
252
253-- Traditionally we use these unique names (so that we can flatten the lookup list
254-- (we create subsets runtime) but I will adapt the old code to newer names.
255
256-- chainsub
257-- reversesub
258
259local lookupnames = {
260    gsub = {
261        single                      = "gsub_single",
262        multiple                    = "gsub_multiple",
263        alternate                   = "gsub_alternate",
264        ligature                    = "gsub_ligature",
265        context                     = "gsub_context",
266        chainedcontext              = "gsub_contextchain",
267        reversechainedcontextsingle = "gsub_reversecontextchain", -- reversesub
268    },
269    gpos = {
270        single                      = "gpos_single",
271        pair                        = "gpos_pair",
272        cursive                     = "gpos_cursive",
273        marktobase                  = "gpos_mark2base",
274        marktoligature              = "gpos_mark2ligature",
275        marktomark                  = "gpos_mark2mark",
276        context                     = "gpos_context",
277        chainedcontext              = "gpos_contextchain",
278    }
279}
280
281-- keep this as reference:
282--
283-- local lookupbits = {
284--     [0x0001] = "righttoleft",
285--     [0x0002] = "ignorebaseglyphs",
286--     [0x0004] = "ignoreligatures",
287--     [0x0008] = "ignoremarks",
288--     [0x0010] = "usemarkfilteringset",
289--     [0x00E0] = "reserved",
290--     [0xFF00] = "markattachmenttype",
291-- }
292--
293-- local lookupstate = setmetatableindex(function(t,k)
294--     local v = { }
295--     for kk, vv in next, lookupbits do
296--         if (k & kk) ~= 0 then
297--             v[vv] = true
298--         end
299--     end
300--     t[k] = v
301--     return v
302-- end)
303
304local lookupflags = setmetatableindex(function(t,k)
305    local v = {
306        (k & 0x0008) ~= 0 and true or false, -- ignoremarks
307        (k & 0x0004) ~= 0 and true or false, -- ignoreligatures
308        (k & 0x0002) ~= 0 and true or false, -- ignorebaseglyphs
309        (k & 0x0001) ~= 0 and true or false, -- r2l
310    }
311    t[k] = v
312    return v
313end)
314
315-- Variation stores: it's not entirely clear if the regions are a shared
316-- resource (it looks like they are). Anyway, we play safe and use a
317-- share.
318
319-- values can be anything the min/max permits so we can either think of
320-- real values of a fraction along the axis (probably easier)
321
322-- wght=400,wdth=100,ital=1
323
324local function axistofactors(str)
325    local t = settings_to_hash(str)
326    for k, v in next, t do
327        t[k] = tonumber(v) or v -- this also normalizes numbers itself
328    end
329    return t
330end
331
332local hash = table.setmetatableindex(function(t,k)
333    local v = sequenced(axistofactors(k),",")
334    t[k] = v
335    return v
336end)
337
338helpers.normalizedaxishash = hash
339
340local cleanname = fonts.names and fonts.names.cleanname or function(name)
341    return name and (gsub(lower(name),"[^%a%d]","")) or nil
342end
343
344helpers.cleanname = cleanname
345
346function helpers.normalizedaxis(str)
347    return hash[str] or str
348end
349
350-- contradicting spec ... (signs) so i'll check it and fix it once we have
351-- proper fonts
352
353local function getaxisscale(segments,minimum,default,maximum,user)
354    --
355    -- returns the right values cf example in standard
356    --
357    if not minimum or not default or not maximum then
358        return false
359    end
360    if user < minimum then
361        user = minimum
362    elseif user > maximum then
363        user = maximum
364    end
365    if user < default then
366        default = - (default - user) / (default - minimum)
367    elseif user > default then
368        default = (user - default) / (maximum - default)
369    else
370        default = 0
371    end
372    if not segments then
373        return default
374    end
375    local e
376    for i=1,#segments do
377        local s = segments[i]
378        if type(s) ~= "number" then
379         -- report("using default axis scale")
380            return default
381        elseif s[1] >= default then
382            if s[2] == default then
383                return default
384            else
385                e = i
386                break
387            end
388        end
389    end
390    if e then
391        local b = segments[e-1]
392        local e = segments[e]
393        return b[2] + (e[2] - b[2]) * (default - b[1]) / (e[1] - b[1])
394    else
395        return false
396    end
397end
398
399local function getfactors(data,instancespec)
400    if instancespec == true then
401        -- take default
402    elseif type(instancespec) ~= "string" or instancespec == "" then
403        return
404    end
405    local variabledata = data.variabledata
406    if not variabledata then
407        return
408    end
409    local instances = variabledata.instances
410    local axis      = variabledata.axis
411    local segments  = variabledata.segments
412    if instances and axis then
413        local values
414        if instancespec == true then
415            -- first instance:
416         -- values = instances[1].values
417            -- axis defaults:
418            values = { }
419            for i=1,#axis do
420                values[i] = {
421                 -- axis  = axis[i].tag,
422                    value = axis[i].default,
423                }
424            end
425
426        else
427            for i=1,#instances do
428                local instance = instances[i]
429                if cleanname(instance.subfamily) == instancespec then
430                    values = instance.values
431                    break
432                end
433            end
434        end
435        if values then
436            local factors = { }
437            for i=1,#axis do
438                local a = axis[i]
439                factors[i] = getaxisscale(segments,a.minimum,a.default,a.maximum,values[i].value)
440            end
441            return factors
442        end
443        local values = axistofactors(hash[instancespec] or instancespec)
444        if values then
445            local factors = { }
446            for i=1,#axis do
447                local a = axis[i]
448                local d = a.default
449                factors[i] = getaxisscale(segments,a.minimum,d,a.maximum,values[a.name or a.tag] or values[a.tag] or d)
450            end
451            return factors
452        end
453    end
454end
455
456local function getscales(regions,factors)
457    local scales = { }
458    for i=1,#regions do
459        local region = regions[i]
460        local s = 1
461        for j=1,#region do
462            local axis  = region[j]
463            local f     = factors[j]
464            local start = axis.start
465            local peak  = axis.peak
466            local stop  = axis.stop
467            -- get rid of these tests, false flag
468            if start > peak or peak > stop then
469                -- * 1
470            elseif start < 0 and stop > 0 and peak ~= 0 then
471                -- * 1
472            elseif peak == 0 then
473                -- * 1
474            elseif f < start or f > stop then
475                -- * 0
476                s = 0
477                break
478            elseif f < peak then
479             -- s = - s * (f - start) / (peak - start)
480                s = s * (f - start) / (peak - start)
481            elseif f > peak then
482                s = s * (stop - f) / (stop - peak)
483            else
484                -- * 1
485            end
486        end
487        scales[i] = s
488    end
489    return scales
490end
491
492helpers.getaxisscale  = getaxisscale
493helpers.getfactors    = getfactors
494helpers.getscales     = getscales
495helpers.axistofactors = axistofactors
496
497local function readvariationdata(f,storeoffset,factors) -- store
498    local position = getposition(f)
499    setposition(f,storeoffset)
500    -- header
501    local format       = readushort(f)
502    local regionoffset = storeoffset + readulong(f)
503    local nofdeltadata = readushort(f)
504    local deltadata    = readcardinaltable(f,nofdeltadata,ulong)
505    -- regions
506    setposition(f,regionoffset)
507    local nofaxis    = readushort(f)
508    local nofregions = readushort(f)
509    local regions    = { }
510    for i=1,nofregions do -- 0
511        local t = { }
512        for i=1,nofaxis do
513            t[i] = { -- maybe no keys, just 1..3
514                start = read2dot14(f),
515                peak  = read2dot14(f),
516                stop  = read2dot14(f),
517            }
518        end
519        regions[i] = t
520    end
521    -- deltas
522 -- if factors then
523        for i=1,nofdeltadata do
524            setposition(f,storeoffset+deltadata[i])
525            local nofdeltasets = readushort(f)
526            local nofshorts    = readushort(f)
527            local nofregions   = readushort(f)
528            local usedregions  = { }
529            local deltas       = { }
530            for i=1,nofregions do
531                usedregions[i] = regions[readushort(f)+1]
532            end
533            -- we could test before and save a for
534            for i=1,nofdeltasets do
535                local t = readintegertable(f,nofshorts,short)
536                for i=nofshorts+1,nofregions do
537                    t[i] = readinteger(f)
538                end
539                deltas[i] = t
540            end
541            deltadata[i] = {
542                regions = usedregions,
543                deltas  = deltas,
544                scales  = factors and getscales(usedregions,factors) or nil,
545            }
546        end
547 -- end
548    setposition(f,position)
549    return regions, deltadata
550end
551
552helpers.readvariationdata = readvariationdata
553
554-- Beware: only use the simple variant if we don't set keys/values (otherwise too many entries). We
555-- could also have a variant that applies a function but there is no real benefit in this.
556
557local function readcoverage(f,offset,simple)
558    setposition(f,offset)
559    local coverageformat = readushort(f)
560    if coverageformat == 1 then
561        local nofcoverage = readushort(f)
562        if simple then
563            -- often 1 or 2
564            if nofcoverage == 1 then
565                return { readushort(f) }
566            elseif nofcoverage == 2 then
567                return { readushort(f), readushort(f) }
568            else
569                return readcardinaltable(f,nofcoverage,ushort)
570            end
571        elseif nofcoverage == 1 then
572            return { [readushort(f)] = 0 }
573        elseif nofcoverage == 2 then
574            return { [readushort(f)] = 0, [readushort(f)] = 1 }
575        else
576            local coverage = { }
577            for i=0,nofcoverage-1 do
578                coverage[readushort(f)] = i -- index in record
579            end
580            return coverage
581        end
582    elseif coverageformat == 2 then
583        local nofranges = readushort(f)
584        local coverage  = { }
585        local n         = simple and 1 or 0 -- needs checking
586        for i=1,nofranges do
587            local firstindex = readushort(f)
588            local lastindex  = readushort(f)
589            local coverindex = readushort(f)
590            if simple then
591                for i=firstindex,lastindex do
592                    coverage[n] = i
593                    n = n + 1
594                end
595            else
596                for i=firstindex,lastindex do
597                    coverage[i] = n
598                    n = n + 1
599                end
600            end
601        end
602        return coverage
603    else
604        report("unknown coverage format %a ",coverageformat)
605        return { }
606    end
607end
608
609local function readclassdef(f,offset,preset)
610    setposition(f,offset)
611    local classdefformat = readushort(f)
612    local classdef = { }
613    if type(preset) == "number" then
614        for k=0,preset-1 do
615            classdef[k] = 1
616        end
617    end
618    if classdefformat == 1 then
619        local index       = readushort(f)
620        local nofclassdef = readushort(f)
621        for i=1,nofclassdef do
622            classdef[index] = readushort(f) + 1
623            index = index + 1
624        end
625    elseif classdefformat == 2 then
626        local nofranges = readushort(f)
627        local n = 0
628        for i=1,nofranges do
629            local firstindex = readushort(f)
630            local lastindex  = readushort(f)
631            local class      = readushort(f) + 1
632            for i=firstindex,lastindex do
633                classdef[i] = class
634            end
635        end
636    else
637        report("unknown classdef format %a ",classdefformat)
638    end
639    if type(preset) == "table" then
640        for k in next, preset do
641            if not classdef[k] then
642                classdef[k] = 1
643            end
644        end
645    end
646    return classdef
647end
648
649local function classtocoverage(defs)
650    if defs then
651        local list = { }
652        for index, class in next, defs do
653            local c = list[class]
654            if c then
655                c[#c+1] = index
656            else
657                list[class] = { index }
658            end
659        end
660        return list
661    end
662end
663
664-- extra readers
665
666local skips = { [0] =
667    0, -- ----
668    1, -- ---x
669    1, -- --y-
670    2, -- --yx
671    1, -- -h--
672    2, -- -h-x
673    2, -- -hy-
674    3, -- -hyx
675    2, -- v--x
676    2, -- v-y-
677    3, -- v-yx
678    2, -- vh--
679    3, -- vh-x
680    3, -- vhy-
681    4, -- vhyx
682}
683
684-- We can assume that 0 is nothing and in fact we can start at 1 as
685-- usual in Lua to make sure of that.
686
687local function readvariation(f,offset)
688    local p = getposition(f)
689    setposition(f,offset)
690    local outer  = readushort(f)
691    local inner  = readushort(f)
692    local format = readushort(f)
693    setposition(f,p)
694    if format == 0x8000 then
695        return outer, inner
696    end
697end
698
699local function readposition(f,format,mainoffset,getdelta)
700    if format == 0 then
701        return false
702    end
703    -- a few happen often
704    if format == 0x04 then
705        local h = readshort(f)
706        if h == 0 then
707            return true -- all zero
708        else
709            return { 0, 0, h, 0 }
710        end
711    end
712    if format == 0x05 then
713        local x = readshort(f)
714        local h = readshort(f)
715        if x == 0 and h == 0 then
716            return true -- all zero
717        else
718            return { x, 0, h, 0 }
719        end
720    end
721    if format == 0x44 then
722        local h = readshort(f)
723        if getdelta then
724            local d = readshort(f) -- short or ushort
725            if d > 0 then
726                local outer, inner = readvariation(f,mainoffset+d)
727                if outer then
728                    h = h + getdelta(outer,inner)
729                end
730            end
731        else
732            skipshort(f,1)
733        end
734        if h == 0 then
735            return true -- all zero
736        else
737            return { 0, 0, h, 0 }
738        end
739    end
740    --
741    -- todo:
742    --
743    -- if format == 0x55 then
744    --     local x = readshort(f)
745    --     local h = readshort(f)
746    --     ....
747    -- end
748    --
749    local x = (format & 0x1) ~= 0 and readshort(f) or 0 -- x placement
750    local y = (format & 0x2) ~= 0 and readshort(f) or 0 -- y placement
751    local h = (format & 0x4) ~= 0 and readshort(f) or 0 -- h advance
752    local v = (format & 0x8) ~= 0 and readshort(f) or 0 -- v advance
753    if format >= 0x10 then
754        local X = (format & 0x10) ~= 0 and skipshort(f) or 0
755        local Y = (format & 0x20) ~= 0 and skipshort(f) or 0
756        local H = (format & 0x40) ~= 0 and skipshort(f) or 0
757        local V = (format & 0x80) ~= 0 and skipshort(f) or 0
758     -- local s = skips[extract(format,4,4)]
759        local s = skips[(format >> 4) & 0xF]
760        if s > 0 then
761            skipshort(f,s)
762        end
763        if getdelta then
764            if X > 0 then
765                local outer, inner = readvariation(f,mainoffset+X)
766                if outer then
767                    x = x + getdelta(outer,inner)
768                end
769            end
770            if Y > 0 then
771                local outer, inner = readvariation(f,mainoffset+Y)
772                if outer then
773                    y = y + getdelta(outer,inner)
774                end
775            end
776            if H > 0 then
777                local outer, inner = readvariation(f,mainoffset+H)
778                if outer then
779                    h = h + getdelta(outer,inner)
780                end
781            end
782            if V > 0 then
783                local outer, inner = readvariation(f,mainoffset+V)
784                if outer then
785                    v = v + getdelta(outer,inner)
786                end
787            end
788        end
789        return { x, y, h, v }
790    elseif x == 0 and y == 0 and h == 0 and v == 0 then
791        return true -- all zero
792    else
793        return { x, y, h, v }
794    end
795end
796
797local function readanchor(f,offset,getdelta) -- maybe also ignore 0's as in pos
798    if not offset or offset == 0 then
799        return nil -- false
800    end
801    setposition(f,offset)
802    -- no need to skip as we position each
803    local format = readshort(f) -- 1: x y 2: x y index 3 x y X Y
804    local x = readshort(f)
805    local y = readshort(f)
806    if format == 3 then
807        if getdelta then
808            local X = readshort(f)
809            local Y = readshort(f)
810            if X > 0 then
811                local outer, inner = readvariation(f,offset+X)
812                if outer then
813                    x = x + getdelta(outer,inner)
814                end
815            end
816            if Y > 0 then
817                local outer, inner = readvariation(f,offset+Y)
818                if outer then
819                    y = y + getdelta(outer,inner)
820                end
821            end
822        else
823            skipshort(f,2)
824        end
825        return { x, y } -- , { xindex, yindex }
826    else
827        return { x, y }
828    end
829end
830
831-- common handlers: inlining can be faster but we cache anyway
832-- so we don't bother too much about speed here
833
834local function readfirst(f,offset)
835    if offset then
836        setposition(f,offset)
837    end
838    return { readushort(f) }
839end
840
841-- quite often 0, 1, 2
842
843local function readarray(f,offset)
844    if offset then
845        setposition(f,offset)
846    end
847    local n = readushort(f)
848    if n == 1 then
849        return { readushort(f) }, 1
850    elseif n > 0 then
851        return readcardinaltable(f,n,ushort), n
852    end
853end
854
855local function readcoveragearray(f,offset,t,simple)
856    if not t then
857        return nil
858    end
859    local n = #t
860    if n == 0 then
861        return nil
862    end
863    for i=1,n do
864        t[i] = readcoverage(f,offset+t[i],simple)
865    end
866    return t
867end
868
869local function covered(subset,all)
870    local used, u
871    for i=1,#subset do
872        local s = subset[i]
873        if all[s] then
874            if used then
875                u = u + 1
876                used[u] = s
877            else
878                u = 1
879                used = { s }
880            end
881        end
882    end
883    return used
884end
885
886-- We generalize the chained lookups so that we can do with only one handler
887-- when processing them.
888
889-- pruned
890
891local function readlookuparray(f,noflookups,nofcurrent)
892    local lookups = { }
893    if noflookups > 0 then
894        local length = 0
895        for i=1,noflookups do
896            local index = readushort(f) + 1
897            if index > length then
898                length = index
899            end
900            local lookup = readushort(f) + 1
901            local list   = lookups[index]
902            if list then
903                list[#list+1] = lookup
904            else
905                lookups[index] = { lookup }
906            end
907        end
908        for index=1,length do
909            if not lookups[index] then
910                lookups[index] = false
911            end
912        end
913     -- if length > nofcurrent then
914     --     report("more lookups than currently matched characters")
915     -- end
916    end
917    return lookups
918end
919
920-- not pruned
921--
922-- local function readlookuparray(f,noflookups,nofcurrent)
923--     local lookups = { }
924--     for i=1,nofcurrent do
925--         lookups[i] = false
926--     end
927--     for i=1,noflookups do
928--         local index = readushort(f) + 1
929--         if index > nofcurrent then
930--             report("more lookups than currently matched characters")
931--             for i=nofcurrent+1,index-1 do
932--                 lookups[i] = false
933--             end
934--             nofcurrent = index
935--         end
936--         lookups[index] = readushort(f) + 1
937--     end
938--     return lookups
939-- end
940
941local function unchainedcontext(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,what)
942    local tableoffset = lookupoffset + offset
943    setposition(f,tableoffset)
944    local subtype = readushort(f)
945    if subtype == 1 then
946        local coverage     = readushort(f)
947        local subclasssets = readarray(f)
948        local rules        = { }
949        if subclasssets then
950            coverage = readcoverage(f,tableoffset+coverage,true)
951            for i=1,#subclasssets do
952                local offset = subclasssets[i]
953                if offset > 0 then
954                    local firstcoverage = coverage[i]
955                    local rulesoffset   = tableoffset + offset
956                    local subclassrules = readarray(f,rulesoffset)
957                    for rule=1,#subclassrules do
958                        setposition(f,rulesoffset + subclassrules[rule])
959                        local nofcurrent = readushort(f)
960                        local noflookups = readushort(f)
961                        local current    = { { firstcoverage } }
962                        for i=2,nofcurrent do
963                            current[i] = { readushort(f) }
964                        end
965                        local lookups = readlookuparray(f,noflookups,nofcurrent)
966                        rules[#rules+1] = {
967                            current = current,
968                            lookups = lookups
969                        }
970                    end
971                end
972            end
973        else
974            report("empty subclassset in %a subtype %i","unchainedcontext",subtype)
975        end
976        return {
977            format = "glyphs",
978            rules  = rules,
979        }
980    elseif subtype == 2 then
981        -- We expand the classes as later on we do a pack over the whole table so then we get
982        -- back efficiency. This way we can also apply the coverage to the first current.
983        local coverage        = readushort(f)
984        local currentclassdef = readushort(f)
985        local subclasssets    = readarray(f)
986        local rules           = { }
987        if subclasssets then
988            coverage             = readcoverage(f,tableoffset + coverage)
989            currentclassdef      = readclassdef(f,tableoffset + currentclassdef,coverage)
990            local currentclasses = classtocoverage(currentclassdef,fontdata.glyphs)
991            for class=1,#subclasssets do
992                local offset = subclasssets[class]
993                if offset > 0 then
994                    local firstcoverage = currentclasses[class]
995                    if firstcoverage then
996                        firstcoverage = covered(firstcoverage,coverage) -- bonus
997                        if firstcoverage then
998                            local rulesoffset   = tableoffset + offset
999                            local subclassrules = readarray(f,rulesoffset)
1000                            for rule=1,#subclassrules do
1001                                setposition(f,rulesoffset + subclassrules[rule])
1002                                local nofcurrent = readushort(f)
1003                                local noflookups = readushort(f)
1004                                local current    = { firstcoverage }
1005                                for i=2,nofcurrent do
1006                                    current[i] = currentclasses[readushort(f) + 1]
1007                                end
1008                                local lookups = readlookuparray(f,noflookups,nofcurrent)
1009                                rules[#rules+1] = {
1010                                    current = current,
1011                                    lookups = lookups
1012                                }
1013                            end
1014                        else
1015                            report(" ge")
1016                        end
1017                    else
1018                        report("no coverage class")
1019                    end
1020                end
1021            end
1022        else
1023            report("empty subclassset in %a subtype %i","unchainedcontext",subtype)
1024        end
1025        return {
1026            format = "class",
1027            rules  = rules,
1028        }
1029    elseif subtype == 3 then
1030        local nofglyphs  = readushort(f)
1031        local noflookups = readushort(f)
1032        local current    = readcardinaltable(f,nofglyphs,ushort)
1033        local lookups    = readlookuparray(f,noflookups,#current)
1034        current = readcoveragearray(f,tableoffset,current,true)
1035        return {
1036            format = "coverage",
1037            rules  = {
1038                {
1039                    current = current,
1040                    lookups = lookups,
1041                }
1042            }
1043        }
1044    else
1045        report("unsupported subtype %a in %a %s",subtype,"unchainedcontext",what)
1046    end
1047end
1048
1049-- todo: optimize for n=1 ?
1050
1051-- class index needs checking, probably no need for +1
1052
1053local function chainedcontext(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,what)
1054    local tableoffset = lookupoffset + offset
1055    setposition(f,tableoffset)
1056    local subtype = readushort(f)
1057    if subtype == 1 then
1058        local coverage     = readushort(f)
1059        local subclasssets = readarray(f)
1060        local rules        = { }
1061        if subclasssets then
1062            coverage = readcoverage(f,tableoffset+coverage,true)
1063            for i=1,#subclasssets do
1064                local offset = subclasssets[i]
1065                if offset > 0 then
1066                    local firstcoverage = coverage[i]
1067                    local rulesoffset   = tableoffset + offset
1068                    local subclassrules = readarray(f,rulesoffset)
1069                    for rule=1,#subclassrules do
1070                        setposition(f,rulesoffset + subclassrules[rule])
1071                        local nofbefore = readushort(f)
1072                        local before
1073                        if nofbefore > 0 then
1074                            before = { }
1075                            for i=1,nofbefore do
1076                                before[i] = { readushort(f) }
1077                            end
1078                        end
1079                        local nofcurrent = readushort(f)
1080                        local current    = { { firstcoverage } }
1081                        for i=2,nofcurrent do
1082                            current[i] = { readushort(f) }
1083                        end
1084                        local nofafter = readushort(f)
1085                        local after
1086                        if nofafter > 0 then
1087                            after = { }
1088                            for i=1,nofafter do
1089                                after[i] = { readushort(f) }
1090                            end
1091                        end
1092                        local noflookups = readushort(f)
1093                        local lookups    = readlookuparray(f,noflookups,nofcurrent)
1094                        rules[#rules+1] = {
1095                            before  = before,
1096                            current = current,
1097                            after   = after,
1098                            lookups = lookups,
1099                        }
1100                    end
1101                end
1102            end
1103        else
1104            report("empty subclassset in %a subtype %i","chainedcontext",subtype)
1105        end
1106        return {
1107            format = "glyphs",
1108            rules  = rules,
1109        }
1110    elseif subtype == 2 then
1111        local coverage        = readushort(f)
1112        local beforeclassdef  = readushort(f)
1113        local currentclassdef = readushort(f)
1114        local afterclassdef   = readushort(f)
1115        local subclasssets    = readarray(f)
1116        local rules           = { }
1117        if subclasssets then
1118            local coverage        = readcoverage(f,tableoffset + coverage)
1119            local beforeclassdef  = readclassdef(f,tableoffset + beforeclassdef,nofglyphs)
1120            local currentclassdef = readclassdef(f,tableoffset + currentclassdef,coverage)
1121            local afterclassdef   = readclassdef(f,tableoffset + afterclassdef,nofglyphs)
1122            local beforeclasses   = classtocoverage(beforeclassdef,fontdata.glyphs)
1123            local currentclasses  = classtocoverage(currentclassdef,fontdata.glyphs)
1124            local afterclasses    = classtocoverage(afterclassdef,fontdata.glyphs)
1125            for class=1,#subclasssets do
1126                local offset = subclasssets[class]
1127                if offset > 0 then
1128                    local firstcoverage = currentclasses[class]
1129                    if firstcoverage then
1130                        firstcoverage = covered(firstcoverage,coverage) -- bonus
1131                        if firstcoverage then
1132                            local rulesoffset   = tableoffset + offset
1133                            local subclassrules = readarray(f,rulesoffset)
1134                            for rule=1,#subclassrules do
1135                                -- watch out, in context we first get the counts and then the arrays while
1136                                -- here we get them mixed
1137                                setposition(f,rulesoffset + subclassrules[rule])
1138                                local nofbefore = readushort(f)
1139                                local before
1140                                if nofbefore > 0 then
1141                                    before = { }
1142                                    for i=1,nofbefore do
1143                                        before[i] = beforeclasses[readushort(f) + 1]
1144                                    end
1145                                end
1146                                local nofcurrent = readushort(f)
1147                                local current    = { firstcoverage }
1148                                for i=2,nofcurrent do
1149                                    current[i] = currentclasses[readushort(f)+ 1]
1150                                end
1151                                local nofafter = readushort(f)
1152                                local after
1153                                if nofafter > 0 then
1154                                    after = { }
1155                                    for i=1,nofafter do
1156                                        after[i] = afterclasses[readushort(f) + 1]
1157                                    end
1158                                end
1159                                -- no sequence index here (so why in context as it saves nothing)
1160                                local noflookups = readushort(f)
1161                                local lookups    = readlookuparray(f,noflookups,nofcurrent)
1162                                rules[#rules+1] = {
1163                                    before  = before,
1164                                    current = current,
1165                                    after   = after,
1166                                    lookups = lookups,
1167                                }
1168                            end
1169                        else
1170                            report("no coverage")
1171                        end
1172                    else
1173                        report("class is not covered")
1174                    end
1175                end
1176            end
1177        else
1178            report("empty subclassset in %a subtype %i","chainedcontext",subtype)
1179        end
1180        return {
1181            format = "class",
1182            rules  = rules,
1183        }
1184    elseif subtype == 3 then
1185        -- Maybe this one needs checking. Anyway zero current is bad.
1186        local before     = readarray(f)
1187        local current    = readarray(f)
1188        local after      = readarray(f)
1189        local noflookups = readushort(f)
1190        local lookups    = current and readlookuparray(f,noflookups,#current)
1191        if lookups then
1192            before  = readcoveragearray(f,tableoffset,before,true)
1193            current = readcoveragearray(f,tableoffset,current,true)
1194            after   = readcoveragearray(f,tableoffset,after,true)
1195            return {
1196                format = "coverage",
1197                rules  = {
1198                    {
1199                        before  = before,
1200                        current = current,
1201                        after   = after,
1202                        lookups = lookups,
1203                    }
1204                }
1205            }
1206        else
1207            report("confusing subtype %a in %a %s",subtype,"chainedcontext",what)
1208        end
1209    else
1210        report("unsupported subtype %a in %a %s",subtype,"chainedcontext",what)
1211    end
1212end
1213
1214local function extension(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,types,handlers,what)
1215    local tableoffset = lookupoffset + offset
1216    setposition(f,tableoffset)
1217    local subtype = readushort(f)
1218    if subtype == 1 then
1219        local lookuptype = types[readushort(f)]
1220        local faroffset  = readulong(f)
1221        local handler    = handlers[lookuptype]
1222        if handler then
1223            -- maybe we can just pass one offset (or tableoffset first)
1224            return handler(f,fontdata,lookupid,tableoffset + faroffset,0,glyphs,nofglyphs), lookuptype
1225        else
1226            report("no handler for lookuptype %a subtype %a in %s %s",lookuptype,subtype,what,"extension")
1227        end
1228    else
1229        report("unsupported subtype %a in %s %s",subtype,what,"extension")
1230    end
1231end
1232
1233-- gsub handlers
1234
1235function gsubhandlers.single(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1236    local tableoffset = lookupoffset + offset
1237    setposition(f,tableoffset)
1238    local subtype = readushort(f)
1239    if subtype == 1 then
1240        local coverage = readushort(f)
1241        local delta    = readshort(f) -- can be negative
1242        local coverage = readcoverage(f,tableoffset+coverage) -- not simple as we need to set key/value anyway
1243        for index in next, coverage do
1244            local newindex = (index + delta) % 65536 -- modulo is new in 1.8.3
1245            if index > nofglyphs or newindex > nofglyphs then
1246                report("invalid index in %s format %i: %i -> %i (max %i)","single",subtype,index,newindex,nofglyphs)
1247                coverage[index] = nil
1248            else
1249                coverage[index] = newindex
1250            end
1251        end
1252        return {
1253            coverage = coverage
1254        }
1255    elseif subtype == 2 then -- in streamreader a seek and fetch is faster than a temp table
1256        local coverage        = readushort(f)
1257        local nofreplacements = readushort(f)
1258        local replacements    = readcardinaltable(f,nofreplacements,ushort)
1259        local coverage = readcoverage(f,tableoffset + coverage) -- not simple as we need to set key/value anyway
1260        for index, newindex in next, coverage do
1261            newindex = newindex + 1
1262            if index > nofglyphs or newindex > nofglyphs then
1263                report("invalid index in %s format %i: %i -> %i (max %i)","single",subtype,index,newindex,nofglyphs)
1264                coverage[index] = nil
1265            else
1266                coverage[index] = replacements[newindex]
1267            end
1268        end
1269        return {
1270            coverage = coverage
1271        }
1272    else
1273        report("unsupported subtype %a in %a substitution",subtype,"single")
1274    end
1275end
1276
1277-- we see coverage format 0x300 in some old ms fonts
1278
1279local function sethandler(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,what)
1280    local tableoffset = lookupoffset + offset
1281    setposition(f,tableoffset)
1282    local subtype = readushort(f)
1283    if subtype == 1 then
1284        local coverage    = readushort(f)
1285        local nofsequence = readushort(f)
1286        local sequences   = readcardinaltable(f,nofsequence,ushort)
1287        for i=1,nofsequence do
1288            setposition(f,tableoffset + sequences[i])
1289            sequences[i] = readcardinaltable(f,readushort(f),ushort)
1290        end
1291        local coverage = readcoverage(f,tableoffset + coverage)
1292        for index, newindex in next, coverage do
1293            newindex = newindex + 1
1294            if index > nofglyphs or newindex > nofglyphs then
1295                report("invalid index in %s format %i: %i -> %i (max %i)",what,subtype,index,newindex,nofglyphs)
1296                coverage[index] = nil
1297            else
1298                coverage[index] = sequences[newindex]
1299            end
1300        end
1301        return {
1302            coverage = coverage
1303        }
1304    else
1305        report("unsupported subtype %a in %a substitution",subtype,what)
1306    end
1307end
1308
1309function gsubhandlers.multiple(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1310    return sethandler(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,"multiple")
1311end
1312
1313function gsubhandlers.alternate(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1314    return sethandler(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,"alternate")
1315end
1316
1317function gsubhandlers.ligature(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1318    local tableoffset = lookupoffset + offset
1319    setposition(f,tableoffset)
1320    local subtype = readushort(f)
1321    if subtype == 1 then
1322        local coverage  = readushort(f)
1323        local nofsets   = readushort(f)
1324        local ligatures = readcardinaltable(f,nofsets,ushort)
1325        for i=1,nofsets do
1326            local offset = lookupoffset + offset + ligatures[i]
1327            setposition(f,offset)
1328            local n = readushort(f)
1329            if n == 1 then
1330                ligatures[i] = { offset + readushort(f) }
1331            else
1332                local l = { }
1333                for i=1,n do
1334                    l[i] = offset + readushort(f)
1335                end
1336                ligatures[i] = l
1337            end
1338        end
1339        local coverage = readcoverage(f,tableoffset + coverage)
1340        for index, newindex in next, coverage do
1341            local hash = { }
1342            local ligatures = ligatures[newindex+1]
1343            for i=1,#ligatures do
1344                local offset = ligatures[i]
1345                setposition(f,offset)
1346                local lig = readushort(f)
1347                local cnt = readushort(f)
1348                local hsh = hash
1349                for i=2,cnt do
1350                    local c = readushort(f)
1351                    local h = hsh[c]
1352                    if not h then
1353                        h = { }
1354                        hsh[c] = h
1355                    end
1356                    hsh =  h
1357                end
1358                hsh.ligature = lig
1359            end
1360            coverage[index] = hash
1361        end
1362        return {
1363            coverage = coverage
1364        }
1365    else
1366        report("unsupported subtype %a in %a substitution",subtype,"ligature")
1367    end
1368end
1369
1370function gsubhandlers.context(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1371    return unchainedcontext(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,"substitution"), "context"
1372end
1373
1374function gsubhandlers.chainedcontext(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1375    return chainedcontext(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,"substitution"), "chainedcontext"
1376end
1377
1378function gsubhandlers.extension(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1379    return extension(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,gsubtypes,gsubhandlers,"substitution")
1380end
1381
1382function gsubhandlers.reversechainedcontextsingle(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1383    local tableoffset = lookupoffset + offset
1384    setposition(f,tableoffset)
1385    local subtype = readushort(f)
1386    if subtype == 1 then -- NEEDS CHECKING
1387        local current      = readfirst(f)
1388        local before       = readarray(f)
1389        local after        = readarray(f)
1390        local replacements = readarray(f)
1391        current = readcoveragearray(f,tableoffset,current,true)
1392        before  = readcoveragearray(f,tableoffset,before,true)
1393        after   = readcoveragearray(f,tableoffset,after,true)
1394        return {
1395            format = "reversecoverage", -- reversesub
1396            rules  = {
1397                {
1398                    before       = before,
1399                    current      = current,
1400                    after        = after,
1401                    replacements = replacements,
1402                }
1403            }
1404        }, "reversechainedcontextsingle"
1405    else
1406        report("unsupported subtype %a in %a substitution",subtype,"reversechainedcontextsingle")
1407    end
1408end
1409
1410-- gpos handlers
1411
1412local function readpairsets(f,tableoffset,sets,format1,format2,mainoffset,getdelta)
1413    local done = { }
1414    for i=1,#sets do
1415        local offset = sets[i]
1416        local reused = done[offset]
1417        if not reused then
1418            offset = tableoffset + offset
1419            setposition(f,offset)
1420            local n = readushort(f)
1421            reused = { }
1422            for i=1,n do
1423                reused[i] = {
1424                    readushort(f), -- second glyph id
1425                    readposition(f,format1,offset,getdelta),
1426                    readposition(f,format2,offset,getdelta),
1427                }
1428            end
1429            done[offset] = reused
1430        end
1431        sets[i] = reused
1432    end
1433    return sets
1434end
1435
1436local function readpairclasssets(f,nofclasses1,nofclasses2,format1,format2,mainoffset,getdelta)
1437    local classlist1  = { }
1438    for i=1,nofclasses1 do
1439        local classlist2 = { }
1440        classlist1[i] = classlist2
1441        for j=1,nofclasses2 do
1442            local one = readposition(f,format1,mainoffset,getdelta)
1443            local two = readposition(f,format2,mainoffset,getdelta)
1444            if one or two then
1445                classlist2[j] = { one, two }
1446            else
1447                classlist2[j] = false
1448            end
1449        end
1450    end
1451    return classlist1
1452end
1453
1454-- no real gain in kerns as we pack
1455
1456function gposhandlers.single(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1457    local tableoffset = lookupoffset + offset
1458    setposition(f,tableoffset)
1459    local subtype  = readushort(f)
1460    local getdelta = fontdata.temporary.getdelta
1461    if subtype == 1 then
1462        local coverage = readushort(f)
1463        local format   = readushort(f)
1464        local value    = readposition(f,format,tableoffset,getdelta)
1465        local coverage = readcoverage(f,tableoffset+coverage)
1466        for index, newindex in next, coverage do
1467            coverage[index] = value -- will be packed and shared anyway
1468        end
1469        return {
1470            format   = "single",
1471            coverage = coverage,
1472        }
1473    elseif subtype == 2 then
1474        local coverage  = readushort(f)
1475        local format    = readushort(f)
1476        local nofvalues = readushort(f)
1477        local values    = { }
1478        for i=1,nofvalues do
1479            values[i] = readposition(f,format,tableoffset,getdelta)
1480        end
1481        local coverage = readcoverage(f,tableoffset+coverage)
1482        for index, newindex in next, coverage do
1483            coverage[index] = values[newindex+1]
1484        end
1485        return {
1486            format   = "single",
1487            coverage = coverage,
1488        }
1489    else
1490        report("unsupported subtype %a in %a positioning",subtype,"single")
1491    end
1492end
1493
1494-- this needs checking! if no second pair then another advance over the list
1495
1496-- ValueFormat1 applies to the ValueRecord of the first glyph in each pair. ValueRecords for all first glyphs must use ValueFormat1. If ValueFormat1 is set to zero (0), the corresponding glyph has no ValueRecord and, therefore, should not be repositioned.
1497-- ValueFormat2 applies to the ValueRecord of the second glyph in each pair. ValueRecords for all second glyphs must use ValueFormat2. If ValueFormat2 is set to null, then the second glyph of the pair is the “next” glyph for which a lookup should be performed.
1498
1499-- local simple = {
1500--     [true]  = { [true] = { true,  true }, [false] = { true  } },
1501--     [false] = { [true] = { false, true }, [false] = { false } },
1502-- }
1503
1504-- function gposhandlers.pair(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1505--     local tableoffset = lookupoffset + offset
1506--     setposition(f,tableoffset)
1507--     local subtype  = readushort(f)
1508--     local getdelta = fontdata.temporary.getdelta
1509--     if subtype == 1 then
1510--         local coverage = readushort(f)
1511--         local format1  = readushort(f)
1512--         local format2  = readushort(f)
1513--         local sets     = readarray(f)
1514--               sets     = readpairsets(f,tableoffset,sets,format1,format2,mainoffset,getdelta)
1515--               coverage = readcoverage(f,tableoffset + coverage)
1516--         local shared   = { } -- partial sparse, when set also needs to be handled in the packer
1517--         for index, newindex in next, coverage do
1518--             local set  = sets[newindex+1]
1519--             local hash = { }
1520--             for i=1,#set do
1521--                 local value = set[i]
1522--                 if value then
1523--                     local other  = value[1]
1524--                     if shared then
1525--                         local s = shared[value]
1526--                         if s == nil then
1527--                             local first  = value[2]
1528--                             local second = value[3]
1529--                             if first or second then
1530--                                 s = { first, second or nil } -- needs checking
1531--                             else
1532--                                 s = false
1533--                             end
1534--                             shared[value] = s
1535--                         end
1536--                         hash[other] = s or nil
1537--                     else
1538--                         local first  = value[2]
1539--                         local second = value[3]
1540--                         if first or second then
1541--                             hash[other] = { first, second or nil } -- needs checking
1542--                         else
1543--                             hash[other] = nil -- what if set, maybe warning
1544--                         end
1545--                     end
1546--                 end
1547--             end
1548--             coverage[index] = hash
1549--         end
1550--         return {
1551--             shared   = shared and true or nil,
1552--             format   = "pair",
1553--             coverage = coverage,
1554--         }
1555--     elseif subtype == 2 then
1556--         local coverage     = readushort(f)
1557--         local format1      = readushort(f)
1558--         local format2      = readushort(f)
1559--         local classdef1    = readushort(f)
1560--         local classdef2    = readushort(f)
1561--         local nofclasses1  = readushort(f) -- incl class 0
1562--         local nofclasses2  = readushort(f) -- incl class 0
1563--         local classlist    = readpairclasssets(f,nofclasses1,nofclasses2,format1,format2,tableoffset,getdelta)
1564--               coverage     = readcoverage(f,tableoffset+coverage)
1565--               classdef1    = readclassdef(f,tableoffset+classdef1,coverage)
1566--               classdef2    = readclassdef(f,tableoffset+classdef2,nofglyphs)
1567--         local usedcoverage = { }
1568--         local shared       = { } -- partial sparse, when set also needs to be handled in the packer
1569--         for g1, c1 in next, classdef1 do
1570--             if coverage[g1] then
1571--                 local l1 = classlist[c1]
1572--                 if l1 then
1573--                     local hash = { }
1574--                     for paired, class in next, classdef2 do
1575--                         local offsets = l1[class]
1576--                         if offsets then
1577--                             local first  = offsets[1]
1578--                             local second = offsets[2]
1579--                             if first or second then
1580--                                 if shared then
1581--                                     local s1 = shared[first]
1582--                                     if s1 == nil then
1583--                                         s1 = { }
1584--                                         shared[first] = s1
1585--                                     end
1586--                                     local s2 = s1[second]
1587--                                     if s2 == nil then
1588--                                         s2 = { first, second or nil }
1589--                                         s1[second] = s2
1590--                                     end
1591--                                     hash[paired] = s2
1592--                                 else
1593--                                     hash[paired] = { first, second or nil }
1594--                                 end
1595--                             else
1596--                                 -- upto the next lookup for this combination
1597--                             end
1598--                         end
1599--                     end
1600--                     usedcoverage[g1] = hash
1601--                 end
1602--             end
1603--         end
1604--         return {
1605--             shared   = shared and true or nil,
1606--             format   = "pair",
1607--             coverage = usedcoverage,
1608--         }
1609--     elseif subtype == 3 then
1610--         report("yet unsupported subtype %a in %a positioning",subtype,"pair")
1611--     else
1612--         report("unsupported subtype %a in %a positioning",subtype,"pair")
1613--     end
1614-- end
1615
1616function gposhandlers.pair(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1617    local tableoffset = lookupoffset + offset
1618    setposition(f,tableoffset)
1619    local subtype  = readushort(f)
1620    local getdelta = fontdata.temporary.getdelta
1621    if subtype == 1 then
1622        local coverage = readushort(f)
1623        local format1  = readushort(f)
1624        local format2  = readushort(f)
1625        local sets     = readarray(f)
1626              sets     = readpairsets(f,tableoffset,sets,format1,format2,mainoffset,getdelta)
1627              coverage = readcoverage(f,tableoffset + coverage)
1628        local shared   = { } -- partial sparse, when set also needs to be handled in the packer
1629        for index, newindex in next, coverage do
1630            local set  = sets[newindex+1]
1631            local hash = { }
1632            for i=1,#set do
1633                local value = set[i]
1634                if value then
1635                    local other = value[1]
1636                    local share = shared[value]
1637                    if share == nil then
1638                        local first  = value[2]
1639                        local second = value[3]
1640                        if first or second then
1641                            share = { first, second or nil } -- needs checking
1642                        else
1643                            share = false
1644                        end
1645                        shared[value] = share
1646                    end
1647                    hash[other] = share or nil -- really overload ?
1648                end
1649            end
1650            coverage[index] = hash
1651        end
1652        return {
1653            shared   = shared and true or nil,
1654            format   = "pair",
1655            coverage = coverage,
1656        }
1657    elseif subtype == 2 then
1658        local coverage     = readushort(f)
1659        local format1      = readushort(f)
1660        local format2      = readushort(f)
1661        local classdef1    = readushort(f)
1662        local classdef2    = readushort(f)
1663        local nofclasses1  = readushort(f) -- incl class 0
1664        local nofclasses2  = readushort(f) -- incl class 0
1665        local classlist    = readpairclasssets(f,nofclasses1,nofclasses2,format1,format2,tableoffset,getdelta)
1666              coverage     = readcoverage(f,tableoffset+coverage)
1667              classdef1    = readclassdef(f,tableoffset+classdef1,coverage)
1668              classdef2    = readclassdef(f,tableoffset+classdef2,nofglyphs)
1669        local usedcoverage = { }
1670        local shared       = { } -- partial sparse, when set also needs to be handled in the packer
1671        for g1, c1 in next, classdef1 do
1672            if coverage[g1] then
1673                local l1 = classlist[c1]
1674                if l1 then
1675                    local hash = { }
1676                    for paired, class in next, classdef2 do
1677                        local offsets = l1[class]
1678                        if offsets then
1679                            local first  = offsets[1]
1680                            local second = offsets[2]
1681                            if first or second then
1682                                local s1 = shared[first]
1683                                if s1 == nil then
1684                                    s1 = { }
1685                                    shared[first] = s1
1686                                end
1687                                local s2 = s1[second]
1688                                if s2 == nil then
1689                                    s2 = { first, second or nil }
1690                                    s1[second] = s2
1691                                end
1692                                hash[paired] = s2
1693                            end
1694                        end
1695                    end
1696                    usedcoverage[g1] = hash
1697                end
1698            end
1699        end
1700        return {
1701            shared   = shared and true or nil,
1702            format   = "pair",
1703            coverage = usedcoverage,
1704        }
1705    elseif subtype == 3 then
1706        report("yet unsupported subtype %a in %a positioning",subtype,"pair")
1707    else
1708        report("unsupported subtype %a in %a positioning",subtype,"pair")
1709    end
1710end
1711
1712function gposhandlers.cursive(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1713    local tableoffset = lookupoffset + offset
1714    setposition(f,tableoffset)
1715    local subtype  = readushort(f)
1716    local getdelta = fontdata.temporary.getdelta
1717    if subtype == 1 then
1718        local coverage   = tableoffset + readushort(f)
1719        local nofrecords = readushort(f)
1720        local records    = { }
1721        for i=1,nofrecords do
1722            local entry = readushort(f)
1723            local exit  = readushort(f)
1724            records[i] = {
1725             -- entry = entry ~= 0 and (tableoffset + entry) or false,
1726             -- exit  = exit  ~= 0 and (tableoffset + exit ) or nil,
1727                entry ~= 0 and (tableoffset + entry) or false,
1728                exit  ~= 0 and (tableoffset + exit ) or nil,
1729            }
1730        end
1731        -- slot 1 will become hash after loading and it must be unique because we
1732        -- pack the tables (packed we turn the cc-* into a zero)
1733        local cc = (fontdata.temporary.cursivecount or 0) + 1
1734        fontdata.temporary.cursivecount = cc
1735        cc = "cc-" .. cc
1736        coverage = readcoverage(f,coverage)
1737        for i=1,nofrecords do
1738            local r = records[i]
1739            records[i] = {
1740             -- 1,
1741                cc,
1742             -- readanchor(f,r.entry,getdelta) or false,
1743             -- readanchor(f,r.exit, getdelta) or nil,
1744                readanchor(f,r[1],getdelta) or false,
1745                readanchor(f,r[2],getdelta) or nil,
1746            }
1747        end
1748        for index, newindex in next, coverage do
1749            coverage[index] = records[newindex+1]
1750        end
1751        return {
1752            coverage = coverage,
1753        }
1754    else
1755        report("unsupported subtype %a in %a positioning",subtype,"cursive")
1756    end
1757end
1758
1759local function handlemark(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,ligature)
1760    local tableoffset = lookupoffset + offset
1761    setposition(f,tableoffset)
1762    local subtype  = readushort(f)
1763    local getdelta = fontdata.temporary.getdelta
1764    if subtype == 1 then
1765        -- we are one based, not zero
1766        local markcoverage = tableoffset + readushort(f)
1767        local basecoverage = tableoffset + readushort(f)
1768        local nofclasses   = readushort(f)
1769        local markoffset   = tableoffset + readushort(f)
1770        local baseoffset   = tableoffset + readushort(f)
1771        --
1772        local markcoverage = readcoverage(f,markcoverage)
1773        local basecoverage = readcoverage(f,basecoverage,true) -- TO BE CHECKED: true
1774        --
1775        setposition(f,markoffset)
1776        local markclasses    = { }
1777        local nofmarkclasses = readushort(f)
1778        --
1779        local lastanchor  = fontdata.lastanchor or 0
1780        local usedanchors = { }
1781        --
1782        for i=1,nofmarkclasses do
1783            local class  = readushort(f) + 1
1784            local offset = readushort(f)
1785            if offset == 0 then
1786                markclasses[i] = false
1787            else
1788                markclasses[i] = { class, markoffset + offset }
1789            end
1790            usedanchors[class] = true
1791        end
1792        for i=1,nofmarkclasses do
1793            local mc = markclasses[i]
1794            if mc then
1795                mc[2] = readanchor(f,mc[2],getdelta)
1796            end
1797        end
1798        --
1799        setposition(f,baseoffset)
1800        local nofbaserecords = readushort(f)
1801        local baserecords    = { }
1802        --
1803        if ligature then
1804            -- 3 components
1805            -- 1 : class .. nofclasses -- NULL when empty
1806            -- 2 : class .. nofclasses -- NULL when empty
1807            -- 3 : class .. nofclasses -- NULL when empty
1808            for i=1,nofbaserecords do -- here i is the class
1809                local offset = readushort(f)
1810                if offset == 0 then
1811                    baserecords[i] = false
1812                else
1813                    baserecords[i] = baseoffset + offset
1814                end
1815            end
1816            for i=1,nofbaserecords do
1817                local recordoffset = baserecords[i]
1818                if recordoffset then
1819                    setposition(f,recordoffset)
1820                    local nofcomponents = readushort(f)
1821                    local components = { }
1822                    for i=1,nofcomponents do
1823                        local classes = { }
1824                        for i=1,nofclasses do
1825                            local offset = readushort(f)
1826                            if offset ~= 0 then
1827                                classes[i] = recordoffset + offset
1828                            else
1829                                classes[i] = false
1830                            end
1831                        end
1832                        components[i] = classes
1833                    end
1834                    baserecords[i] = components
1835                end
1836            end
1837            local baseclasses = { } -- setmetatableindex("table")
1838            for i=1,nofclasses do
1839                baseclasses[i] = { }
1840            end
1841            for i=1,nofbaserecords do
1842                local components = baserecords[i]
1843                if components then
1844                    local b = basecoverage[i]
1845                    for c=1,#components do
1846                        local classes = components[c]
1847                        if classes then
1848                            for i=1,nofclasses do
1849                                local anchor = readanchor(f,classes[i],getdelta)
1850                                local bclass = baseclasses[i]
1851                                local bentry = bclass[b]
1852                                if bentry then
1853                                    bentry[c] = anchor
1854                                else
1855                                    bclass[b]= { [c] = anchor }
1856                                end
1857                            end
1858                        end
1859                    end
1860                end
1861            end
1862            for index, newindex in next, markcoverage do
1863                markcoverage[index] = markclasses[newindex+1] or nil
1864            end
1865            return {
1866                format      = "ligature",
1867                baseclasses = baseclasses,
1868                coverage    = markcoverage,
1869            }
1870        else
1871            for i=1,nofbaserecords do
1872                local r = { }
1873                for j=1,nofclasses do
1874                    local offset = readushort(f)
1875                    if offset == 0 then
1876                        r[j] = false
1877                    else
1878                        r[j] = baseoffset + offset
1879                    end
1880                end
1881                baserecords[i] = r
1882            end
1883            local baseclasses = { } -- setmetatableindex("table")
1884            for i=1,nofclasses do
1885                baseclasses[i] = { }
1886            end
1887            for i=1,nofbaserecords do
1888                local r = baserecords[i]
1889                local b = basecoverage[i]
1890                for j=1,nofclasses do
1891                    baseclasses[j][b] = readanchor(f,r[j],getdelta)
1892                end
1893            end
1894            for index, newindex in next, markcoverage do
1895                markcoverage[index] = markclasses[newindex+1] or nil
1896            end
1897            -- we could actually already calculate the displacement if we want
1898            return {
1899                format      = "base",
1900                baseclasses = baseclasses,
1901                coverage    = markcoverage,
1902            }
1903        end
1904    else
1905        report("unsupported subtype %a in",subtype)
1906    end
1907
1908end
1909
1910function gposhandlers.marktobase(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1911    return handlemark(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1912end
1913
1914function gposhandlers.marktoligature(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1915    return handlemark(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,true)
1916end
1917
1918function gposhandlers.marktomark(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1919    return handlemark(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1920end
1921
1922function gposhandlers.context(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1923    return unchainedcontext(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,"positioning"), "context"
1924end
1925
1926function gposhandlers.chainedcontext(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1927    return chainedcontext(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,"positioning"), "chainedcontext"
1928end
1929
1930function gposhandlers.extension(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs)
1931    return extension(f,fontdata,lookupid,lookupoffset,offset,glyphs,nofglyphs,gpostypes,gposhandlers,"positioning")
1932end
1933
1934-- main loader
1935
1936do
1937
1938    local plugins = { }
1939
1940    function plugins.size(f,fontdata,tableoffset,feature)
1941        if fontdata.designsize then
1942            -- yes, there are fonts with multiple size entries ... it probably relates
1943            -- to the other two fields (menu entries in some language)
1944        else
1945            local function check(offset)
1946                setposition(f,offset)
1947                local designsize = readushort(f)
1948                if designsize > 0 then -- we could also have a threshold
1949                    local fontstyleid = readushort(f)
1950                    local guimenuid   = readushort(f)
1951                    local minsize     = readushort(f)
1952                    local maxsize     = readushort(f)
1953                    if minsize == 0 and maxsize == 0 and fontstyleid == 0 and guimenuid == 0 then
1954                        minsize = designsize
1955                        maxsize = designsize
1956                    end
1957                    if designsize >= minsize and designsize <= maxsize then
1958                        return minsize, maxsize, designsize
1959                    end
1960                end
1961            end
1962            local minsize, maxsize, designsize = check(tableoffset+feature.offset+feature.parameters)
1963            if not designsize then
1964                -- some old adobe fonts have: tableoffset+feature.parameters and we could
1965                -- use some heuristic but why bother ... this extra check will be removed
1966                -- some day and/or when we run into an issue
1967                minsize, maxsize, designsize = check(tableoffset+feature.parameters)
1968                if designsize then
1969                    report("bad size feature in %a, falling back to wrong offset",fontdata.filename or "?")
1970                else
1971                    report("bad size feature in %a,",fontdata.filename or "?")
1972                end
1973            end
1974            if designsize then
1975                fontdata.minsize    = minsize
1976                fontdata.maxsize    = maxsize
1977                fontdata.designsize = designsize
1978            end
1979        end
1980    end
1981
1982 -- function plugins.rvrn(f,fontdata,tableoffset,feature)
1983 --     -- todo, at least a message
1984 -- end
1985
1986    -- feature order needs checking ... as we loop over a hash ... however, in the file
1987    -- they are sorted so order is not that relevant
1988
1989    local function reorderfeatures(fontdata,scripts,features)
1990        local scriptlangs  = { }
1991        local featurehash  = { }
1992        local featureorder = { }
1993        for script, languages in next, scripts do
1994            for language, record in next, languages do
1995                local hash = { }
1996                local list = record.featureindices
1997                for k=1,#list do
1998                    local index   = list[k]
1999                    local feature = features[index]
2000                    local lookups = feature.lookups
2001                    local tag     = feature.tag
2002                    if tag then
2003                        hash[tag] = true
2004                    end
2005                    if lookups then
2006                        for i=1,#lookups do
2007                            local lookup = lookups[i]
2008                            local o = featureorder[lookup]
2009                            if o then
2010                                local okay = true
2011                                for i=1,#o do
2012                                    if o[i] == tag then
2013                                        okay = false
2014                                        break
2015                                    end
2016                                end
2017                                if okay then
2018                                    o[#o+1] = tag
2019                                end
2020                            else
2021                                featureorder[lookup] = { tag }
2022                            end
2023                            local f = featurehash[lookup]
2024                            if f then
2025                                local h = f[tag]
2026                                if h then
2027                                    local s = h[script]
2028                                    if s then
2029                                        s[language] = true
2030                                    else
2031                                        h[script] = { [language] = true }
2032                                    end
2033                                else
2034                                    f[tag] = { [script] = { [language] = true } }
2035                                end
2036                            else
2037                                featurehash[lookup] = { [tag] = { [script] = { [language] = true } } }
2038                            end
2039                            --
2040                            local h = scriptlangs[tag]
2041                            if h then
2042                                local s = h[script]
2043                                if s then
2044                                    s[language] = true
2045                                else
2046                                    h[script] = { [language] = true }
2047                                end
2048                            else
2049                                scriptlangs[tag] = { [script] = { [language] = true } }
2050                            end
2051                        end
2052                    end
2053                end
2054            end
2055        end
2056        return scriptlangs, featurehash, featureorder
2057    end
2058
2059    local function readscriplan(f,fontdata,scriptoffset)
2060        setposition(f,scriptoffset)
2061        local nofscripts = readushort(f)
2062        local scripts    = { }
2063        for i=1,nofscripts do
2064            scripts[readtag(f)] = scriptoffset + readushort(f)
2065        end
2066        -- script list -> language system info
2067        local languagesystems = setmetatableindex("table")
2068        for script, offset in next, scripts do
2069            setposition(f,offset)
2070            local defaultoffset = readushort(f)
2071            local noflanguages  = readushort(f)
2072            local languages     = { }
2073            if defaultoffset > 0 then
2074                languages.dflt = languagesystems[offset + defaultoffset]
2075            end
2076            for i=1,noflanguages do
2077                local language      = readtag(f)
2078                local offset        = offset + readushort(f)
2079                languages[language] = languagesystems[offset]
2080            end
2081            scripts[script] = languages
2082        end
2083        -- script list -> language system info -> feature list
2084        for offset, usedfeatures in next, languagesystems do
2085            if offset > 0 then
2086                setposition(f,offset)
2087                local featureindices        = { }
2088                usedfeatures.featureindices = featureindices
2089                usedfeatures.lookuporder    = readushort(f) -- reserved, not used (yet)
2090                usedfeatures.requiredindex  = readushort(f) -- relates to required (can be 0xFFFF)
2091                local noffeatures           = readushort(f)
2092                for i=1,noffeatures do
2093                    featureindices[i] = readushort(f) + 1
2094                end
2095            end
2096        end
2097        return scripts
2098    end
2099
2100    local function readfeatures(f,fontdata,featureoffset)
2101        setposition(f,featureoffset)
2102        local features    = { }
2103        local noffeatures = readushort(f)
2104        for i=1,noffeatures do
2105            -- also shared?
2106            features[i] = {
2107                tag    = readtag(f),
2108                offset = readushort(f)
2109            }
2110        end
2111        --
2112        for i=1,noffeatures do
2113            local feature = features[i]
2114            local offset  = featureoffset+feature.offset
2115            setposition(f,offset)
2116            local parameters = readushort(f) -- feature.parameters
2117            local noflookups = readushort(f)
2118            if noflookups > 0 then
2119--                 local lookups   = { }
2120--                 feature.lookups = lookups
2121--                 for j=1,noflookups do
2122--                     lookups[j] = readushort(f) + 1
2123--                 end
2124                local lookups   = readcardinaltable(f,noflookups,ushort)
2125                feature.lookups = lookups
2126                for j=1,noflookups do
2127                    lookups[j] = lookups[j] + 1
2128                end
2129            end
2130            if parameters > 0 then
2131                feature.parameters = parameters
2132                local plugin = plugins[feature.tag]
2133                if plugin then
2134                    plugin(f,fontdata,featureoffset,feature)
2135                end
2136            end
2137        end
2138        return features
2139    end
2140
2141    local function readlookups(f,lookupoffset,lookuptypes,featurehash,featureorder,nofmarkclasses)
2142        setposition(f,lookupoffset)
2143        local noflookups = readushort(f)
2144        local lookups    = readcardinaltable(f,noflookups,ushort)
2145        for lookupid=1,noflookups do
2146            local offset = lookups[lookupid]
2147            setposition(f,lookupoffset+offset)
2148            local subtables    = { }
2149            local typebits     = readushort(f)
2150            local flagbits     = readushort(f)
2151            local lookuptype   = lookuptypes[typebits]
2152            local lookupflags  = lookupflags[flagbits]
2153            local nofsubtables = readushort(f)
2154            for j=1,nofsubtables do
2155                subtables[j] = offset + readushort(f) -- we can probably put lookupoffset here
2156            end
2157            -- which one wins?
2158            local markclass = (flagbits & 0x0010) ~= 0 -- usemarkfilteringset
2159            local markset   = (flagbits >> 8) & 0xFFFFFFFF
2160            if markclass then
2161                markclass = nofmarkclasses + markset
2162            end
2163            if markset > 0 then
2164                markclass = nofmarkclasses + markset
2165            end
2166            lookups[lookupid] = {
2167                type      = lookuptype,
2168             -- chain     = chaindirections[lookuptype] or nil,
2169                flags     = lookupflags,
2170                name      = lookupid,
2171                subtables = subtables,
2172                markclass = markclass,
2173                features  = featurehash[lookupid], -- not if extension
2174                order     = featureorder[lookupid],
2175            }
2176        end
2177        return lookups
2178    end
2179
2180    local f_lookupname = formatters["%s_%s_%s"]
2181
2182    local function resolvelookups(f,lookupoffset,fontdata,lookups,lookuptypes,lookuphandlers,what,tableoffset)
2183
2184        local sequences      = fontdata.sequences  or { }
2185        local sublookuplist  = fontdata.sublookups or { }
2186        fontdata.sequences   = sequences
2187        fontdata.sublookups  = sublookuplist
2188        local nofsublookups  = #sublookuplist
2189        local nofsequences   = #sequences -- 0
2190        local lastsublookup  = nofsublookups
2191        local lastsequence   = nofsequences
2192        local lookupnames    = lookupnames[what]
2193        local sublookuphash  = { }
2194        local sublookupcheck = { }
2195        local glyphs         = fontdata.glyphs
2196        local nofglyphs      = fontdata.nofglyphs or #glyphs
2197        local noflookups     = #lookups
2198        local lookupprefix   = sub(what,2,2) -- g[s|p][ub|os]
2199        --
2200        local usedlookups    = false -- setmetatableindex("number")
2201        --
2202        local allsteps = { } -- new per 2022-09-25
2203
2204        for lookupid=1,noflookups do
2205            local lookup     = lookups[lookupid]
2206            local lookuptype = lookup.type
2207            local subtables  = lookup.subtables
2208            local features   = lookup.features
2209            local handler    = lookuphandlers[lookuptype]
2210            if handler then
2211                local nofsubtables = #subtables
2212                local order        = lookup.order
2213                local flags        = lookup.flags
2214                -- this is expected in the font handler (faster checking)
2215                if flags[1] then flags[1] = "mark" end
2216                if flags[2] then flags[2] = "ligature" end
2217                if flags[3] then flags[3] = "base" end
2218                --
2219                local markclass    = lookup.markclass
2220             -- local chain        = lookup.chain
2221                if nofsubtables > 0 then
2222                    local steps     = { }
2223                    local nofsteps  = 0
2224                    local oldtype   = nil
2225                    for s=1,nofsubtables do
2226                        local step, lt = handler(f,fontdata,lookupid,lookupoffset,subtables[s],glyphs,nofglyphs)
2227                        if lt then
2228                            lookuptype = lt
2229                            if oldtype and lt ~= oldtype then
2230                                report("messy %s lookup type %a and %a",what,lookuptype,oldtype)
2231                            end
2232                            oldtype = lookuptype
2233                        end
2234                        if not step then
2235                            report("unsupported %s lookup type %a",what,lookuptype)
2236                        else
2237                            nofsteps = nofsteps + 1
2238                            steps[nofsteps] = step
2239                            local rules = step.rules
2240                            if rules then
2241                                allsteps[#allsteps+1] = step -- new per 2022-09-25
2242                                for i=1,#rules do
2243                                    local rule         = rules[i]
2244                                    local before       = rule.before
2245                                    local current      = rule.current
2246                                    local after        = rule.after
2247                                    local replacements = rule.replacements
2248                                    if before then
2249                                        for i=1,#before do
2250                                            before[i] = tohash(before[i])
2251                                        end
2252                                        -- as with original ctx ff loader
2253                                        rule.before = reversed(before)
2254                                    end
2255                                    if current then
2256                                        if replacements then
2257                                            -- We have a reverse lookup and therefore only one current entry. We might need
2258                                            -- to reverse the order in the before and after lists so that needs checking.
2259                                            local first = current[1]
2260                                            local hash  = { }
2261                                            local repl  = { }
2262                                            for i=1,#first do
2263                                                local c = first[i]
2264                                                hash[c] = true
2265                                                repl[c] = replacements[i]
2266                                            end
2267                                            rule.current      = { hash }
2268                                            rule.replacements = repl
2269                                        else
2270                                            for i=1,#current do
2271                                                current[i] = tohash(current[i])
2272                                            end
2273                                        end
2274                                    else
2275                                        -- weird lookup
2276                                    end
2277                                    if after then
2278                                        for i=1,#after do
2279                                            after[i] = tohash(after[i])
2280                                        end
2281                                    end
2282                                    if usedlookups then
2283                                        local lookups = rule.lookups
2284                                        if lookups then
2285                                            for k, v in next, lookups do
2286                                                if v then
2287                                                    for k, v in next, v do
2288                                                        usedlookups[v] = usedlookups[v] + 1
2289                                                    end
2290                                                end
2291                                            end
2292                                        end
2293                                    end
2294                                end
2295                            end
2296                        end
2297                    end
2298                    if nofsteps ~= nofsubtables then
2299                        report("bogus subtables removed in %s lookup type %a",what,lookuptype)
2300                    end
2301                    lookuptype = lookupnames[lookuptype] or lookuptype
2302                    if features then
2303                        nofsequences = nofsequences + 1
2304                     -- report("registering %i as sequence step %i",lookupid,nofsequences)
2305                        local l = {
2306                            index     = nofsequences,
2307                            name      = f_lookupname(lookupprefix,"s",lookupid+lookupidoffset),
2308                            steps     = steps,
2309                            nofsteps  = nofsteps,
2310                            type      = lookuptype,
2311                            markclass = markclass or nil,
2312                            flags     = flags,
2313                         -- chain     = chain,
2314                            order     = order,
2315                            features  = features,
2316                        }
2317                        sequences[nofsequences] = l
2318                        lookup.done = l
2319                    else
2320                        nofsublookups = nofsublookups + 1
2321                     -- report("registering %i as sublookup %i",lookupid,nofsublookups)
2322                        local l = {
2323                            index     = nofsublookups,
2324                            name      = f_lookupname(lookupprefix,"l",lookupid+lookupidoffset),
2325                            steps     = steps,
2326                            nofsteps  = nofsteps,
2327                            type      = lookuptype,
2328                            markclass = markclass or nil,
2329                            flags     = flags,
2330                         -- chain     = chain,
2331                        }
2332                        sublookuplist[nofsublookups] = l
2333                        sublookuphash[lookupid] = nofsublookups
2334                        sublookupcheck[lookupid] = 0
2335                        lookup.done = l
2336                    end
2337                else
2338                    report("no subtables for lookup %a",lookupid)
2339                end
2340            else
2341                report("no handler for lookup %a with type %a",lookupid,lookuptype)
2342            end
2343        end
2344
2345        if usedlookups then
2346            report("used %s lookups: % t",what,sortedkeys(usedlookups))
2347        end
2348
2349        -- When we have a context, we have sublookups that resolve into lookups for which we need to
2350        -- know the type. We split the main lookuptable in two parts: sequences (the main lookups)
2351        -- and subtable lookups (simple specs with no features). We could keep them merged and might do
2352        -- that once we only use this loader. Then we can also move the simple specs into the sequence.
2353        -- After all, we pack afterwards.
2354
2355        local reported = { }
2356
2357        local function report_issue(i,what,step,kind)
2358--             if not reported[step] then
2359                report("rule %i in step %i of %s has %s lookups",i,step,what,kind)
2360--                 reported[name] = true
2361--             end
2362        end
2363
2364     -- for i=lastsequence+1,nofsequences do
2365     --     local sequence = sequences[i]
2366     --     local steps    = sequence.steps
2367     --     for i=1,#steps do
2368     --         local step  = steps[i]
2369
2370            for s=1,#allsteps do          -- new per 2022-09-25
2371                local step  = allsteps[s] -- new per 2022-09-25
2372                local rules = step.rules
2373                if rules then
2374                    for i=1,#rules do
2375                        local rule     = rules[i]
2376                        local rlookups = rule.lookups
2377                        if not rlookups then
2378                            report_issue(i,what,s,"no")
2379                        elseif not next(rlookups) then
2380                            -- can be ok as it aborts a chain sequence
2381                         -- report_issue(i,what,s,"empty")
2382                            rule.lookups = nil
2383                        else
2384                            -- we can have holes in rlookups flagged false and we can have multiple lookups
2385                            -- applied (first time seen in seguemj)
2386                            local length = #rlookups
2387                            for index=1,length do
2388                                local lookuplist = rlookups[index]
2389                                if lookuplist then
2390                                    local length   = #lookuplist
2391                                    local found    = { }
2392                                    local noffound = 0
2393                                    for index=1,length do
2394                                        local lookupid = lookuplist[index]
2395                                        if lookupid then
2396                                            local h = sublookuphash[lookupid]
2397                                            if not h then
2398                                                -- here we have a lookup that is used independent as well
2399                                                -- as in another one
2400                                                local lookup = lookups[lookupid]
2401                                                if lookup then
2402                                                    local d = lookup.done
2403                                                    if d then
2404                                                        nofsublookups = nofsublookups + 1
2405                                                     -- report("registering %i as sublookup %i",lookupid,nofsublookups)
2406                                                        local l = {
2407                                                            index     = nofsublookups, -- handy for tracing
2408                                                            name      = f_lookupname(lookupprefix,"d",lookupid+lookupidoffset),
2409                                                            derived   = true,          -- handy for tracing
2410                                                            steps     = d.steps,
2411                                                            nofsteps  = d.nofsteps,
2412                                                            type      = d.lookuptype or "gsub_single", -- todo: check type
2413                                                            markclass = d.markclass or nil,
2414                                                            flags     = d.flags,
2415                                                         -- chain     = d.chain,
2416                                                        }
2417                                                        sublookuplist[nofsublookups] = copy(l) -- we repack later
2418                                                        sublookuphash[lookupid] = nofsublookups
2419                                                        sublookupcheck[lookupid] = 1
2420                                                        h = nofsublookups
2421                                                    else
2422                                                        report_issue(i,what,s,"missing")
2423                                                        rule.lookups = nil
2424                                                        break
2425                                                    end
2426                                                else
2427                                                    report_issue(i,what,s,"bad")
2428                                                    rule.lookups = nil
2429                                                    break
2430                                                end
2431                                            else
2432                                                sublookupcheck[lookupid] = sublookupcheck[lookupid] + 1
2433                                            end
2434                                            if h then
2435                                                noffound = noffound + 1
2436                                                found[noffound] = h
2437                                            end
2438                                        end
2439                                    end
2440                                    rlookups[index] = noffound > 0 and found or false
2441                                else
2442                                    rlookups[index] = false
2443                                end
2444                            end
2445                        end
2446                    end
2447                end
2448            end
2449     -- end -- new per 2022-09-25
2450
2451        for i, n in sortedhash(sublookupcheck) do
2452            local l = lookups[i]
2453            local t = l.type
2454            if n == 0 and t ~= "extension" then
2455                local d = l.done
2456                report("%s lookup %s of type %a is not used",what,d and d.name or l.name,t)
2457            end
2458        end
2459
2460    end
2461
2462    local function loadvariations(f,fontdata,variationsoffset,lookuptypes,featurehash,featureorder)
2463        setposition(f,variationsoffset)
2464        local version    = readulong(f) -- two times readushort
2465        local nofrecords = readulong(f)
2466        local records    = { }
2467        for i=1,nofrecords do
2468            records[i] = {
2469                conditions    = readulong(f),
2470                substitutions = readulong(f),
2471            }
2472        end
2473        for i=1,nofrecords do
2474            local record = records[i]
2475            local offset = record.conditions
2476            if offset == 0 then
2477                record.condition = nil
2478                record.matchtype = "always"
2479            else
2480                local offset = variationsoffset+offset
2481                setposition(f,offset)
2482                local nofconditions = readushort(f)
2483                local conditions    = { }
2484                for i=1,nofconditions do
2485                    conditions[i] = offset + readulong(f)
2486                end
2487                record.conditions = conditions
2488                record.matchtype  = "condition"
2489            end
2490        end
2491        for i=1,nofrecords do
2492            local record = records[i]
2493            if record.matchtype == "condition" then
2494                local conditions = record.conditions
2495                for i=1,#conditions do
2496                    setposition(f,conditions[i])
2497                    conditions[i] = {
2498                        format   = readushort(f),
2499                        axis     = readushort(f),
2500                        minvalue = read2dot14(f),
2501                        maxvalue = read2dot14(f),
2502                    }
2503                end
2504            end
2505        end
2506
2507        for i=1,nofrecords do
2508            local record = records[i]
2509            local offset = record.substitutions
2510            if offset == 0 then
2511                record.substitutions = { }
2512            else
2513                setposition(f,variationsoffset + offset)
2514                local version          = readulong(f)
2515                local nofsubstitutions = readushort(f)
2516                local substitutions    = { }
2517                for i=1,nofsubstitutions do
2518                    substitutions[readushort(f)] = readulong(f)
2519                end
2520                for index, alternates in sortedhash(substitutions) do
2521                    if index == 0 then
2522                        record.substitutions = false
2523                    else
2524                        local tableoffset = variationsoffset + offset + alternates
2525                        setposition(f,tableoffset)
2526                        local parameters = readulong(f) -- feature parameters
2527                        local noflookups = readushort(f)
2528                        local lookups    = readcardinaltable(f,noflookups,ushort) -- not sure what to do with these
2529                        -- todo : resolve to proper lookups
2530                        record.substitutions = lookups
2531                    end
2532                end
2533            end
2534        end
2535        setvariabledata(fontdata,"features",records)
2536    end
2537
2538    local function readscripts(f,fontdata,what,lookuptypes,lookuphandlers,lookupstoo)
2539        local tableoffset = gotodatatable(f,fontdata,what,true)
2540        if tableoffset then
2541            local version          = readulong(f)
2542            local scriptoffset     = tableoffset + readushort(f)
2543            local featureoffset    = tableoffset + readushort(f)
2544            local lookupoffset     = tableoffset + readushort(f)
2545            -- MFK : Rubik-Regular.ttf : we need to delay adding the offset
2546         -- local variationsoffset = version > 0x00010000 and (tableoffset + readulong(f)) or 0
2547            local variationsoffset = version > 0x00010000 and readulong(f) or 0
2548            if not scriptoffset then
2549                return
2550            end
2551            local scripts  = readscriplan(f,fontdata,scriptoffset)
2552            local features = readfeatures(f,fontdata,featureoffset)
2553            --
2554            local scriptlangs, featurehash, featureorder = reorderfeatures(fontdata,scripts,features)
2555            --
2556            if fontdata.features then
2557                fontdata.features[what] = scriptlangs
2558            else
2559                fontdata.features = { [what] = scriptlangs }
2560            end
2561            --
2562            if not lookupstoo then
2563                return
2564            end
2565            --
2566            local markclasses    = fontdata.markclasses
2567            local marksets       = fontdata.marksets
2568            local nofmarkclasses = (markclasses and #markclasses or 0) - (marksets and #marksets or 0)
2569            local lookups        = readlookups(f,lookupoffset,lookuptypes,featurehash,featureorder,nofmarkclasses)
2570            --
2571            if lookups then
2572                resolvelookups(f,lookupoffset,fontdata,lookups,lookuptypes,lookuphandlers,what,tableoffset)
2573            end
2574            --
2575            if variationsoffset > 0 then
2576             -- loadvariations(f,fontdata,variationsoffset,lookuptypes,featurehash,featureorder)
2577                loadvariations(f,fontdata,tableoffset + variationsoffset,lookuptypes,featurehash,featureorder)
2578            end
2579        end
2580    end
2581
2582    local function checkkerns(f,fontdata,specification)
2583        local datatable = fontdata.tables.kern
2584        if not datatable then
2585            return -- no kerns
2586        end
2587        local features     = fontdata.features
2588        local gposfeatures = features and features.gpos
2589        local name
2590        if not gposfeatures or not gposfeatures.kern then
2591            name = "kern"
2592        elseif specification.globalkerns then
2593            name = "globalkern"
2594        else
2595            report("ignoring global kern table, using gpos kern feature")
2596            return
2597        end
2598        setposition(f,datatable.offset)
2599        local version   = readushort(f)
2600        local noftables = readushort(f)
2601        if noftables > 1 then
2602            report("adding global kern table as gpos feature %a",name)
2603            local kerns = setmetatableindex("table")
2604            for i=1,noftables do
2605                local version  = readushort(f)
2606                local length   = readushort(f)
2607                local coverage = readushort(f)
2608                -- bit 8-15 of coverage: format 0 or 2
2609             -- local format   = rshift(coverage,8) -- is this ok
2610                local format   = (coverage >> 8) & 0xFFFFFFFF -- is this ok
2611                if format == 0 then
2612                    local nofpairs      = readushort(f)
2613                    local searchrange   = readushort(f)
2614                    local entryselector = readushort(f)
2615                    local rangeshift    = readushort(f)
2616                    for i=1,nofpairs do
2617                        kerns[readushort(f)][readushort(f)] = readfword(f)
2618                    end
2619                elseif format == 2 then
2620                    -- apple specific so let's ignore it
2621                else
2622                    -- not supported by ms
2623                end
2624            end
2625            local feature = { dflt = { dflt = true } }
2626            if not features then
2627                fontdata.features = { gpos = { [name] = feature } }
2628            elseif not gposfeatures then
2629                fontdata.features.gpos = { [name] = feature }
2630            else
2631                gposfeatures[name] = feature
2632            end
2633            local sequences = fontdata.sequences
2634            if not sequences then
2635                sequences = { }
2636                fontdata.sequences = sequences
2637            end
2638            local nofsequences = #sequences + 1
2639            sequences[nofsequences] = {
2640                index     = nofsequences,
2641                name      = name,
2642                steps     = {
2643                    {
2644                        coverage = kerns,
2645                        format   = "kern",
2646                    },
2647                },
2648                nofsteps  = 1,
2649                type      = "gpos_pair",
2650                flags     = { false, false, false, false },
2651                order     = { name },
2652                features  = { [name] = feature },
2653            }
2654        else
2655            report("ignoring empty kern table of feature %a",name)
2656        end
2657    end
2658
2659    function readers.gsub(f,fontdata,specification)
2660        if specification.details then
2661            readscripts(f,fontdata,"gsub",gsubtypes,gsubhandlers,specification.lookups)
2662        end
2663    end
2664
2665    function readers.gpos(f,fontdata,specification)
2666        if specification.details then
2667            readscripts(f,fontdata,"gpos",gpostypes,gposhandlers,specification.lookups)
2668            if specification.lookups then
2669                checkkerns(f,fontdata,specification)
2670            end
2671        end
2672    end
2673
2674end
2675
2676function readers.gdef(f,fontdata,specification)
2677    if not specification.glyphs then
2678        return
2679    end
2680    local datatable = fontdata.tables.gdef
2681    if datatable then
2682        local tableoffset = datatable.offset
2683        setposition(f,tableoffset)
2684        local version          = readulong(f)
2685        local classoffset      = readushort(f)
2686        local attachmentoffset = readushort(f) -- used for bitmaps
2687        local ligaturecarets   = readushort(f) -- used in editors (maybe nice for tracing)
2688        local markclassoffset  = readushort(f)
2689        local marksetsoffset   = version >= 0x00010002 and readushort(f) or 0
2690        local varsetsoffset    = version >= 0x00010003 and readulong(f) or 0
2691        local glyphs           = fontdata.glyphs
2692        local marks            = { }
2693        local markclasses      = setmetatableindex("table")
2694        local marksets         = setmetatableindex("table")
2695        fontdata.marks         = marks
2696        fontdata.markclasses   = markclasses
2697        fontdata.marksets      = marksets
2698        -- class definitions
2699        if classoffset ~= 0 then
2700            setposition(f,tableoffset + classoffset)
2701            local classformat = readushort(f)
2702            if classformat == 1 then
2703                local firstindex = readushort(f)
2704                local lastindex  = firstindex + readushort(f) - 1
2705                for index=firstindex,lastindex do
2706                    local class = classes[readushort(f)]
2707                    if class == "mark" then
2708                        marks[index] = true
2709                    end
2710                    glyphs[index].class = class
2711                end
2712            elseif classformat == 2 then
2713                local nofranges = readushort(f)
2714                for i=1,nofranges do
2715                    local firstindex = readushort(f)
2716                    local lastindex  = readushort(f)
2717                    local class      = classes[readushort(f)]
2718                    if class then
2719                        for index=firstindex,lastindex do
2720                            glyphs[index].class = class
2721                            if class == "mark" then
2722                                marks[index] = true
2723                            end
2724                        end
2725                    end
2726                end
2727            end
2728        end
2729        -- mark classes
2730        if markclassoffset ~= 0 then
2731            setposition(f,tableoffset + markclassoffset)
2732            local classformat = readushort(f)
2733            if classformat == 1 then
2734                local firstindex = readushort(f)
2735                local lastindex  = firstindex + readushort(f) - 1
2736                for index=firstindex,lastindex do
2737                    markclasses[readushort(f)][index] = true
2738                end
2739            elseif classformat == 2 then
2740                local nofranges = readushort(f)
2741                for i=1,nofranges do
2742                    local firstindex = readushort(f)
2743                    local lastindex  = readushort(f)
2744                    local class      = markclasses[readushort(f)]
2745                    for index=firstindex,lastindex do
2746                        class[index] = true
2747                    end
2748                end
2749            end
2750        end
2751        -- mark sets
2752        if marksetsoffset ~= 0 then
2753            local nofmarkclasses = fontdata.markclasses and #fontdata.markclasses or 0
2754            marksetsoffset = tableoffset + marksetsoffset
2755            setposition(f,marksetsoffset)
2756            local format = readushort(f)
2757            if format == 1 then
2758                local nofsets = readushort(f)
2759                local sets    = readcardinaltable(f,nofsets,ulong)
2760                for i=1,nofsets do
2761                    local offset = sets[i]
2762                    if offset ~= 0 then
2763                        markclasses[nofmarkclasses + i] = readcoverage(f,marksetsoffset+offset)
2764                        marksets[i] = { }
2765                    end
2766                end
2767            end
2768        end
2769
2770        local factors = specification.factors
2771
2772        if (specification.variable or factors) and varsetsoffset ~= 0 then
2773
2774            local regions, deltas = readvariationdata(f,tableoffset+varsetsoffset,factors)
2775
2776         -- setvariabledata(fontdata,"gregions",regions)
2777
2778            if factors then
2779                fontdata.temporary.getdelta = function(outer,inner)
2780                    local delta = deltas[outer+1]
2781                    if delta then
2782                        local d = delta.deltas[inner+1]
2783                        if d then
2784                            local scales = delta.scales
2785                            local dd = 0
2786                            for i=1,#scales do
2787                                local di = d[i]
2788                                if di then
2789                                    dd = dd + scales[i] * di
2790                                else
2791                                    break
2792                                end
2793                            end
2794                            return round(dd)
2795                        end
2796                    end
2797                    return 0
2798                end
2799            end
2800
2801        end
2802    end
2803end
2804
2805-- We keep this code here instead of font-otm.lua because we need coverage
2806-- helpers. Okay, these helpers could go to the main reader file some day.
2807
2808local function readmathvalue(f)
2809    local v = readshort(f)
2810    skipshort(f,1) -- offset to device table
2811    return v
2812end
2813
2814local function readmathconstants(f,fontdata,offset)
2815    setposition(f,offset)
2816    fontdata.mathconstants = {
2817        ScriptPercentScaleDown                   = readshort(f),
2818        ScriptScriptPercentScaleDown             = readshort(f),
2819        DelimitedSubFormulaMinHeight             = readushort(f),
2820        DisplayOperatorMinHeight                 = readushort(f),
2821        MathLeading                              = readmathvalue(f),
2822        AxisHeight                               = readmathvalue(f),
2823        AccentBaseHeight                         = readmathvalue(f),
2824        FlattenedAccentBaseHeight                = readmathvalue(f),
2825        SubscriptShiftDown                       = readmathvalue(f),
2826        SubscriptTopMax                          = readmathvalue(f),
2827        SubscriptBaselineDropMin                 = readmathvalue(f),
2828        SuperscriptShiftUp                       = readmathvalue(f),
2829        SuperscriptShiftUpCramped                = readmathvalue(f),
2830        SuperscriptBottomMin                     = readmathvalue(f),
2831        SuperscriptBaselineDropMax               = readmathvalue(f),
2832        SubSuperscriptGapMin                     = readmathvalue(f),
2833        SuperscriptBottomMaxWithSubscript        = readmathvalue(f),
2834        SpaceAfterScript                         = readmathvalue(f),
2835        UpperLimitGapMin                         = readmathvalue(f),
2836        UpperLimitBaselineRiseMin                = readmathvalue(f),
2837        LowerLimitGapMin                         = readmathvalue(f),
2838        LowerLimitBaselineDropMin                = readmathvalue(f),
2839        StackTopShiftUp                          = readmathvalue(f),
2840        StackTopDisplayStyleShiftUp              = readmathvalue(f),
2841        StackBottomShiftDown                     = readmathvalue(f),
2842        StackBottomDisplayStyleShiftDown         = readmathvalue(f),
2843        StackGapMin                              = readmathvalue(f),
2844        StackDisplayStyleGapMin                  = readmathvalue(f),
2845        StretchStackTopShiftUp                   = readmathvalue(f),
2846        StretchStackBottomShiftDown              = readmathvalue(f),
2847        StretchStackGapAboveMin                  = readmathvalue(f),
2848        StretchStackGapBelowMin                  = readmathvalue(f),
2849        FractionNumeratorShiftUp                 = readmathvalue(f),
2850        FractionNumeratorDisplayStyleShiftUp     = readmathvalue(f),
2851        FractionDenominatorShiftDown             = readmathvalue(f),
2852        FractionDenominatorDisplayStyleShiftDown = readmathvalue(f),
2853        FractionNumeratorGapMin                  = readmathvalue(f),
2854        FractionNumeratorDisplayStyleGapMin      = readmathvalue(f),
2855        FractionRuleThickness                    = readmathvalue(f),
2856        FractionDenominatorGapMin                = readmathvalue(f),
2857        FractionDenominatorDisplayStyleGapMin    = readmathvalue(f),
2858        SkewedFractionHorizontalGap              = readmathvalue(f),
2859        SkewedFractionVerticalGap                = readmathvalue(f),
2860        OverbarVerticalGap                       = readmathvalue(f),
2861        OverbarRuleThickness                     = readmathvalue(f),
2862        OverbarExtraAscender                     = readmathvalue(f),
2863        UnderbarVerticalGap                      = readmathvalue(f),
2864        UnderbarRuleThickness                    = readmathvalue(f),
2865        UnderbarExtraDescender                   = readmathvalue(f),
2866        RadicalVerticalGap                       = readmathvalue(f),
2867        RadicalDisplayStyleVerticalGap           = readmathvalue(f),
2868        RadicalRuleThickness                     = readmathvalue(f),
2869        RadicalExtraAscender                     = readmathvalue(f),
2870        RadicalKernBeforeDegree                  = readmathvalue(f),
2871        RadicalKernAfterDegree                   = readmathvalue(f),
2872        RadicalDegreeBottomRaisePercent          = readshort(f),
2873    }
2874end
2875
2876local function readmathglyphinfo(f,fontdata,offset)
2877    setposition(f,offset)
2878    local italics    = readushort(f)
2879    local accents    = readushort(f)
2880    local extensions = readushort(f)
2881    local kerns      = readushort(f)
2882    local glyphs     = fontdata.glyphs
2883    if italics ~= 0 then
2884        setposition(f,offset+italics)
2885        local coverage  = readushort(f)
2886        local nofglyphs = readushort(f)
2887        coverage = readcoverage(f,offset+italics+coverage,true)
2888        setposition(f,offset+italics+4)
2889        for i=1,nofglyphs do
2890            local italic = readmathvalue(f)
2891            if italic ~= 0 then
2892                local glyph = glyphs[coverage[i]]
2893                local math  = glyph.math
2894                if not math then
2895                    glyph.math = { italic = italic }
2896                else
2897                    math.italic = italic
2898                end
2899            end
2900        end
2901        fontdata.hasitalics = true
2902    end
2903    if accents ~= 0 then
2904        setposition(f,offset+accents)
2905        local coverage  = readushort(f)
2906        local nofglyphs = readushort(f)
2907        coverage = readcoverage(f,offset+accents+coverage,true)
2908        setposition(f,offset+accents+4)
2909        for i=1,nofglyphs do
2910            local accent = readmathvalue(f)
2911            if accent ~= 0 then
2912                local glyph = glyphs[coverage[i]]
2913                local math  = glyph.math
2914                if not math then
2915                    glyph.math = { accent = accent }
2916                else
2917                    math.accent = accent -- will become math.topanchor
2918                end
2919            end
2920        end
2921    end
2922    if extensions ~= 0 then
2923        setposition(f,offset+extensions)
2924    end
2925    if kerns ~= 0 then
2926        local kernoffset = offset + kerns
2927        setposition(f,kernoffset)
2928        local coverage  = readushort(f)
2929        local nofglyphs = readushort(f)
2930        if nofglyphs > 0 then
2931            local function get(offset)
2932                setposition(f,kernoffset+offset)
2933                local n = readushort(f)
2934                if n == 0 then
2935                    local k = readmathvalue(f)
2936                    if k == 0 then
2937                        -- no need for it (happens sometimes)
2938                    else
2939                        return { { kern = k } }
2940                    end
2941                else
2942                    local l = { }
2943                    for i=1,n do
2944                        l[i] = { height = readmathvalue(f) }
2945                    end
2946                    for i=1,n do
2947                        l[i].kern = readmathvalue(f)
2948                    end
2949                    l[n+1] = { kern = readmathvalue(f) }
2950                    return l
2951                end
2952            end
2953            local kernsets = { }
2954            for i=1,nofglyphs do
2955                local topright    = readushort(f)
2956                local topleft     = readushort(f)
2957                local bottomright = readushort(f)
2958                local bottomleft  = readushort(f)
2959                kernsets[i] = {
2960                    topright    = topright    ~= 0 and topright    or nil,
2961                    topleft     = topleft     ~= 0 and topleft     or nil,
2962                    bottomright = bottomright ~= 0 and bottomright or nil,
2963                    bottomleft  = bottomleft  ~= 0 and bottomleft  or nil,
2964                }
2965            end
2966            coverage = readcoverage(f,kernoffset+coverage,true)
2967            for i=1,nofglyphs do
2968                local kernset = kernsets[i]
2969                if next(kernset) then
2970                    local k = kernset.topright    if k then kernset.topright    = get(k) end
2971                    local k = kernset.topleft     if k then kernset.topleft     = get(k) end
2972                    local k = kernset.bottomright if k then kernset.bottomright = get(k) end
2973                    local k = kernset.bottomleft  if k then kernset.bottomleft  = get(k) end
2974                    if next(kernset) then
2975                        local glyph = glyphs[coverage[i]]
2976                        local math  = glyph.math
2977                        if math then
2978                            math.kerns = kernset
2979                        else
2980                            glyph.math = { kerns = kernset }
2981                        end
2982                    end
2983                end
2984            end
2985        end
2986    end
2987end
2988
2989local function readmathvariants(f,fontdata,offset)
2990    setposition(f,offset)
2991    local glyphs        = fontdata.glyphs
2992    local minoverlap    = readushort(f)
2993    local vcoverage     = readushort(f)
2994    local hcoverage     = readushort(f)
2995    local vnofglyphs    = readushort(f)
2996    local hnofglyphs    = readushort(f)
2997    local vconstruction = readcardinaltable(f,vnofglyphs,ushort)
2998    local hconstruction = readcardinaltable(f,hnofglyphs,ushort)
2999
3000    fontdata.mathconstants.MinConnectorOverlap = minoverlap
3001
3002    -- variants[i] = {
3003    --     glyph   = readushort(f),
3004    --     advance = readushort(f),
3005    -- }
3006
3007    local function get(offset,coverage,nofglyphs,construction,kvariants,kparts,kitalic,korientation,orientation)
3008        if coverage ~= 0 and nofglyphs > 0 then
3009            local coverage = readcoverage(f,offset+coverage,true)
3010            local n = 0
3011            for i=1,nofglyphs do
3012                local c = construction[i]
3013                if c ~= 0 then
3014                    local index = coverage[i]
3015                    local glyph = glyphs[index]
3016                    local math  = glyph.math
3017                    setposition(f,offset+c)
3018                    local assembly    = readushort(f)
3019                    local nofvariants = readushort(f)
3020                    if nofvariants > 0 then
3021                        local variants, v = nil, 0
3022                        for i=1,nofvariants do
3023                            local variant = readushort(f)
3024                            if variant == index then
3025                             -- report("discarding %s variant %04X for %04X, %C","self referencing",variant,index,tonumber(glyph.unicode) or 0xFFFD)
3026                                n = n + 1
3027                            elseif variants then
3028                                v = v + 1
3029                                variants[v] = variant
3030                            else
3031                                v = 1
3032                                variants = { variant }
3033                            end
3034                            skipshort(f)
3035                        end
3036                        if not variants or not next(variants) then
3037                            -- only self
3038                        elseif not math then
3039                            math = { [kvariants] = variants }
3040                            glyph.math = math
3041                        else
3042                            math[kvariants] = variants
3043                        end
3044                    end
3045                    if assembly ~= 0 then
3046                        setposition(f,offset + c + assembly)
3047                        local italic   = readmathvalue(f)
3048                        local nofparts = readushort(f)
3049                        local parts    = { }
3050                        for i=1,nofparts do
3051                            local p = {
3052                                glyph   = readushort(f),
3053                                start   = readushort(f),
3054                                ["end"] = readushort(f),
3055                                advance = readushort(f),
3056                            }
3057                            local flags = readushort(f)
3058                            if (flags & 0x0001) ~= 0 then
3059                                p.extender = 1 -- true
3060                            end
3061                            parts[i] = p
3062                        end
3063                        if not math then
3064                            math = {
3065                                [kparts] = parts
3066                            }
3067                            glyph.math = math
3068                        else
3069                            math[kparts] = parts
3070                        end
3071                        if italic and italic ~= 0 then
3072                            math[kitalic] = italic
3073                        end
3074                        math[korientation] = orientation
3075                    end
3076                end
3077            end
3078            -- There are quite some fonts out there (noto anno 2024) with these so we only report the
3079            -- number. It's often the first entry then.
3080            if n > 0 then
3081                report("discarding %i self referencing %s variant entries",n,orientation)
3082            end
3083            -- There are a few fonts out there (noto anno 2024) that have a variant list with entries
3084            -- that themselve have variants and that gives circular references in a 'next' chain.
3085            for index=1,#glyphs do
3086                local g = glyphs[index]
3087                local m = g.math
3088                if m then
3089                    local v = m[kvariants]
3090                    if v then
3091                        local done = { [index] = true }
3092                        local size = #v
3093                        local i    = 1
3094                        while i <= size do
3095                            local vi = v[i]
3096                            if done[vi] then
3097                                report("discarding %sdirect circular %s variant index 0x%04X for index 0x%04X, %C","",orientation,vi,index,tonumber(g.unicode) or 0xFFFD)
3098                                table.remove(v,i)
3099                                size = size - 1
3100                                goto NEXT
3101                            else
3102                                local gg = glyphs[vi]
3103                                if gg then
3104                                    local mm = gg.math
3105                                    if mm then
3106                                        local vv = mm[kvariants]
3107                                        if vv then
3108                                            report("discarding %sdirect circular %s variant index 0x%04X for index 0x%04X, %C","in",orientation,vi,index,tonumber(g.unicode) or 0xFFFD)
3109                                            table.remove(v,i)
3110                                            size = size - 1
3111                                            goto NEXT
3112                                        end
3113                                    end
3114                                end
3115                                done[vi] = true
3116                            end
3117                            i = i + 1
3118                          ::NEXT::
3119                        end
3120                    end
3121                end
3122            end
3123        end
3124    end
3125    get(offset,hcoverage,hnofglyphs,hconstruction,"variants","parts","partsitalic","partsorientation","horizontal")
3126    get(offset,vcoverage,vnofglyphs,vconstruction,"variants","parts","partsitalic","partsorientation","vertical")
3127end
3128
3129function readers.math(f,fontdata,specification)
3130    local tableoffset = gotodatatable(f,fontdata,"math",specification.glyphs)
3131    if tableoffset then
3132        local version = readulong(f)
3133     -- if version ~= 0x00010000 then
3134     --     report("table version %a of %a is not supported (yet), maybe font %s is bad",version,"math",fontdata.filename)
3135     --     return
3136     -- end
3137        local constants = readushort(f)
3138        local glyphinfo = readushort(f)
3139        local variants  = readushort(f)
3140        if constants == 0 then
3141            report("the math table of %a has no constants",fontdata.filename)
3142        else
3143            readmathconstants(f,fontdata,tableoffset+constants)
3144        end
3145        if glyphinfo ~= 0 then
3146            readmathglyphinfo(f,fontdata,tableoffset+glyphinfo)
3147        end
3148        if variants ~= 0 then
3149            readmathvariants(f,fontdata,tableoffset+variants)
3150        end
3151    end
3152end
3153
3154do
3155
3156    -- format 1: PaintColrLayers
3157    --     for each referenced child paint table, in bottom-up z-order:
3158    --         call renderPaint() passing the child paint table
3159    --         compose the returned graphic onto the surface using simplealpha blending
3160    --
3161    -- format 2, 3: PaintSolid
3162    --     paint the specified color onto the surface
3163    --
3164    -- format 4, 5, 6, 7, 8, 9: PaintLinearGradient, PaintRadialGradient, PaintSweepGradient
3165    --     paint the gradient onto the surface following the gradient algorithm
3166    --
3167    -- format 10: PaintGlyph
3168    --     apply the outline of the referenced glyph to the clip region
3169    --     (take the intersection of clip regions—see Filling shapes)
3170    --     call renderPaint() passing the child paint table
3171    --     restore the previous clip region
3172    --
3173    -- format 11: PaintColrGlyph
3174    --     call renderPaint() passing the paint table referenced by the base glyph ID
3175    --
3176    -- format 12 .. 31: Transform Translate Scale
3177    --     apply the specified transform, compose the transform with the current transform
3178    --     call renderPaint() passing the child paint table
3179    --     restore the previous transform state
3180    --
3181    -- format 32: PaintComposite
3182    --     call renderPaint() passing the backdrop child paint table and save the result
3183    --     call renderPaint() passing the source child paint table and save the result
3184    --     compose the source and backdrop using the specified composite mode
3185    --     compose the result of the above composition onto the surface using simple alpha blending
3186
3187    local paintdata  -- for the moment verbose, will be just indexed
3188    local linesdata  -- for the moment verbose, will be just indexed
3189    local affinedata -- for the moment verbose, will be just indexed
3190
3191local layerlistoffset
3192local layeroffset
3193
3194local paintindex
3195
3196    local function getpaintoffset(f,offset)
3197        local o = readuoffset(f)
3198        if o == 0 then
3199            --
3200        else
3201            return paintdata[offset+o] -- and offset or nil
3202        end
3203    end
3204
3205    local function getlinesoffset(f,offset,var)
3206        local offset = offset + readuoffset(f)
3207        if linesdata[offset] == nil then
3208            linesdata[offset] = var
3209        end
3210        return offset
3211    end
3212
3213    local function getaffineoffset(f,offset,var)
3214        local offset = offset + readuoffset(f)
3215        if affinedata[offset] == nil then
3216            affinedata[offset] = var
3217        end
3218        return offset
3219    end
3220
3221    local paintreaders = {
3222        -- uint8    numLayers           Number of offsets to paint tables to read from LayerList.
3223        -- uint32   firstLayerIndex     Index (base 0) into the LayerList.
3224       [1] = function(f,format)
3225           return {
3226               format = format,
3227               name   = "PaintColrLayers",
3228               count  = readuinteger(f),
3229               index  = readulong(f),
3230               list   = false,
3231           }
3232       end,
3233       -- uint16   paletteIndex        Index for a CPAL palette entry.
3234       -- F2DOT14  alpha               Alpha value.
3235       [2] = function(f,format)
3236           return {
3237               format  = format,
3238               name    = "Paintsolid",
3239               palette = readushort(f),
3240               alpha   = read2dot14(f),
3241           }
3242       end,
3243       -- uint16   paletteIndex        Index for a CPAL palette entry.
3244       -- F2DOT14  alpha               Alpha value. For variation, use varIndexBase + 0.
3245       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3246       [3] = function(f,format)
3247           return {
3248               format  = format,
3249               name    = "Paintsolid",
3250               palette = readushort(f),
3251               alpha   = read2dot14(f),
3252               varbase = readulong(f),
3253           }
3254       end,
3255       -- Offset24 colorLineOffset     Offset to VarColorLine table.
3256       -- FWORD    x0                  Start point (p₀) x coordinate. For variation, use varIndexBase + 0.
3257       -- FWORD    y0                  Start point (p₀) y coordinate. For variation, use varIndexBase + 1.
3258       -- FWORD    x1                  End point (p₁) x coordinate. For variation, use varIndexBase + 2.
3259       -- FWORD    y1                  End point (p₁) y coordinate. For variation, use varIndexBase + 3.
3260       -- FWORD    x2                  Rotation point (p₂) x coordinate. For variation, use varIndexBase + 4.
3261       -- FWORD    y2                  Rotation point (p₂) y coordinate. For variation, use varIndexBase + 5.
3262       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3263       [4] = function(f,format,offset)
3264           return {
3265               format = format,
3266               name   = "PaintLinearGradient",
3267               color  = getlinesoffset(f,offset,false),
3268               x0     = readfword(f),
3269               y0     = readfword(f),
3270               x1     = readfword(f),
3271               y1     = readfword(f),
3272               x2     = readfword(f),
3273               y2     = readfword(f),
3274           }
3275       end,
3276       [5] = function(f,format,offset)
3277           return {
3278               format  = format,
3279               name    = "PaintLinearGradient",
3280               color   = getlinesoffset(f,offset,true),
3281               x0      = readfword(f),
3282               y0      = readfword(f),
3283               x1      = readfword(f),
3284               y1      = readfword(f),
3285               x2      = readfword(f),
3286               y2      = readfword(f),
3287               varbase = readulong(f),
3288           }
3289       end,
3290       -- Offset24 colorLineOffset     Offset to VarColorLine table.
3291       -- FWORD    x0                  Start circle center x coordinate. For variation, use varIndexBase + 0.
3292       -- FWORD    y0                  Start circle center y coordinate. For variation, use varIndexBase + 1.
3293       -- UFWORD   radius0             Start circle radius. For variation, use varIndexBase + 2.
3294       -- FWORD    x1                  End circle center x coordinate. For variation, use varIndexBase + 3.
3295       -- FWORD    y1                  End circle center y coordinate. For variation, use varIndexBase + 4.
3296       -- UFWORD   radius1             End circle radius. For variation, use varIndexBase + 5.
3297       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3298       [6] = function(f,format,offset)
3299           return {
3300               format  = format,
3301               name    = "PaintRadialGradient",
3302               color   = getlinesoffset(f,offset,false),
3303               x0      = readfword(f),
3304               y0      = readfword(f),
3305               radius0 = readfword(f),
3306               x1      = readfword(f),
3307               y1      = readfword(f),
3308               radius1 = readfword(f),
3309           }
3310       end,
3311       [7] = function(f,format,offset)
3312           return {
3313               format  = format,
3314               name    = "PaintRadialGradient",
3315               color   = getlinesoffset(f,offset,true),
3316               x0      = readfword(f),
3317               y0      = readfword(f),
3318               radius0 = readfword(f),
3319               x1      = readfword(f),
3320               y1      = readfword(f),
3321               radius1 = readfword(f),
3322               varbase = readulong(f),
3323           }
3324       end,
3325       -- Offset24 colorLineOffset     Offset to VarColorLine table.
3326       -- FWORD    centerX             Center x coordinate. For variation, use varIndexBase + 0.
3327       -- FWORD    centerY             Center y coordinate. For variation, use varIndexBase + 1.
3328       -- F2DOT14  startAngle          Start of the angular range of the gradient, 180° in counter-clockwise degrees per 1.0 of value. For variation, use varIndexBase + 2.
3329       -- F2DOT14  endAngle            End of the angular range of the gradient, 180° in counter-clockwise degrees per 1.0 of value. For variation, use varIndexBase + 3.
3330       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3331       [8] = function(f,format,offset)
3332           return {
3333               format     = format,
3334               name       = "PaintSweepGradient",
3335               color      = getlinesoffset(f,offset,false),
3336               centerx    = readfword(f),
3337               centery    = readfword(f),
3338               startangle = read2dot14(f),
3339               endangle   = read2dot14(f),
3340           }
3341       end,
3342       [9] = function(f,format,offset)
3343           return {
3344               format     = format,
3345               name       = "PaintSweepGradient",
3346               color      = getlinesoffset(f,offset,true),
3347               centerx    = readfword(f),
3348               centery    = readfword(f),
3349               startangle = read2dot14(f),
3350               endangle   = read2dot14(f),
3351               varbase    = readulong(f),
3352           }
3353        end,
3354        -- Offset24 paintOffset         Offset to a Paint table.
3355        -- uint16   glyphID             Glyph ID for the source outline.
3356        [10] = function(f,format,offset)
3357            return {
3358                format = format,
3359                name   = "PaintGlyph",
3360                paint  = getpaintoffset(f,offset),
3361                glyph  = readushort(f),
3362            }
3363        end,
3364        -- uint16   glyphID             Glyph ID for a BaseGlyphList base glyph.
3365       [11] = function(f,format)
3366           return {
3367               format = format,
3368               name   = "PaintColrGlyph",
3369               glyph  = readushort(f),
3370           }
3371       end,
3372       -- Offset24 paintOffset         Offset to a Paint subtable.
3373       -- Offset24 transformOffset     Offset to an (Var)Affine2x3 table.
3374       [12] = function(f,format,offset)
3375           return {
3376               format = format,
3377               name   = "PaintTransform",
3378               affine = getaffineoffset(f,offset,false),
3379               paint  = getpaintoffset(f,offset),
3380           }
3381       end,
3382       [13] = function(f,format,offset)
3383           return {
3384               format = format,
3385               name   = "PaintTransform",
3386               affine = getaffineoffset(f,offset,true),
3387               paint  = getpaintoffset(f,offset),
3388           }
3389       end,
3390       -- Offset24 paintOffset         Offset to a Paint subtable.
3391       -- FWORD    dx                  Translation in x direction. For variation, use varIndexBase + 0.
3392       -- FWORD    dy                  Translation in y direction. For variation, use varIndexBase + 1.
3393       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3394       [14] = function(f,format,offset)
3395           return {
3396               format = format,
3397               name   = "PaintTranslate",
3398               paint  = getpaintoffset(f,offset),
3399               dx     = readfword(f),
3400               dy     = readfword(f),
3401           }
3402       end,
3403       [15] = function(f,format,offset)
3404           return {
3405               format  = format,
3406               name    = "PaintTranslate",
3407               paint   = getpaintoffset(f,offset),
3408               dx      = readfword(f),
3409               dy      = readfword(f),
3410               varbase = readulong(f),
3411           }
3412       end,
3413       -- Offset24 paintOffset         Offset to a Paint subtable.
3414       -- F2DOT14  scaleX              Scale factor in x direction. For variation, use varIndexBase + 0.
3415       -- F2DOT14  scaleY              Scale factor in y direction. For variation, use varIndexBase + 1.
3416       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3417       [16] = function(f,format,offset)
3418           return {
3419               format = format,
3420               name   = "PaintScale",
3421               paint  = getpaintoffset(f,offset),
3422               scalex = read2dot14(f),
3423               scaley = read2dot14(f),
3424           }
3425       end,
3426       [17] = function(f,format,offset)
3427           return {
3428               format  = format,
3429               name    = "PaintScale",
3430               paint   = getpaintoffset(f,offset),
3431               scalex  = read2dot14(f),
3432               scaley  = read2dot14(f),
3433               varbase = readulong(f),
3434           }
3435       end,
3436       -- Offset24 paintOffset         Offset to a Paint subtable.
3437       -- F2DOT14  scaleX              Scale factor in x direction. For variation, use varIndexBase + 0.
3438       -- F2DOT14  scaleY              Scale factor in y direction. For variation, use varIndexBase + 1.
3439       -- FWORD    centerX             x coordinate for the center of scaling. For variation, use varIndexBase + 2.
3440       -- FWORD    centerY             y coordinate for the center of scaling. For variation, use varIndexBase + 3.
3441       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3442       [18] = function(f,format,offset)
3443           return {
3444               format  = format,
3445               name    = "PaintScale",
3446               paint   = getpaintoffset(f,offset),
3447               scalex  = read2dot14(f),
3448               scaley  = read2dot14(f),
3449               centerx = readfword(f),
3450               centery = readfword(f),
3451           }
3452       end,
3453       [19] = function(f,format,offset)
3454           return {
3455               format  = format,
3456               name    = "PaintScale",
3457               paint   = getpaintoffset(f,offset),
3458               scalex  = read2dot14(f),
3459               scaley  = read2dot14(f),
3460               centerx = readfword(f),
3461               centery = readfword(f),
3462               varbase = readulong(f),
3463           }
3464       end,
3465       -- Offset24 paintOffset         Offset to a Paint subtable.
3466       -- F2DOT14  scale               Scale factor in x and y directions. For variation, use varIndexBase + 0.
3467       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3468       [20] = function(f,format,offset)
3469           return {
3470               format = format,
3471               name   = "PaintScale",
3472               paint  = getpaintoffset(f,offset),
3473               scale  = read2dot14(f),
3474           }
3475       end,
3476       [21] = function(f,format,offset)
3477           return {
3478               format  = format,
3479               name    = "PaintScale",
3480               paint   = getpaintoffset(f,offset),
3481               scale   = read2dot14(f),
3482               varbase = readulong(f),
3483           }
3484       end,
3485       -- Offset24 paintOffset         Offset to a Paint subtable.
3486       -- F2DOT14  scale               Scale factor in x and y directions. For variation, use varIndexBase + 0.
3487       -- FWORD    centerX             x coordinate for the center of scaling. For variation, use varIndexBase + 1.
3488       -- FWORD    centerY             y coordinate for the center of scaling. For variation, use varIndexBase + 2.
3489       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3490       [22] = function(f,format,offset)
3491           return {
3492               format  = format,
3493               name    = "PaintScale",
3494               paint   = getpaintoffset(f,offset),
3495               scale   = read2dot14(f),
3496               centerx = readfword(f),
3497               centery = readfword(f),
3498           }
3499       end,
3500       [23] = function(f,format,offset)
3501           return {
3502               format  = format,
3503               name    = "PaintScale",
3504               paint   = getpaintoffset(f,offset),
3505               scale   = read2dot14(f),
3506               centerx = readfword(f),
3507               centery = readfword(f),
3508               varbase = readulong(f),
3509           }
3510       end,
3511       -- Offset24 paintOffset         Offset to a Paint subtable.
3512       -- F2DOT14  angle               Rotation angle, 180° in counter-clockwise degrees per 1.0 of value. For variation, use varIndexBase + 0.
3513       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3514       [24] = function(f,format,offset)
3515           return {
3516               format = format,
3517               angle  = read2dot14(f),
3518               paint  = getpaintoffset(f,offset),
3519               name   = "PaintRotate",
3520           }
3521       end,
3522       [25] = function(f,format,offset)
3523           return {
3524               format  = format,
3525               name    = "PaintRotate",
3526               paint   = getpaintoffset(f,offset),
3527               angle   = read2dot14(f),
3528               varbase = readulong(f),
3529           }
3530       end,
3531       -- Offset24 paintOffset         Offset to a Paint subtable.
3532       -- F2DOT14  angle               Rotation angle, 180° in counter-clockwise degrees per 1.0 of value. For variation, use varIndexBase + 0.
3533       -- FWORD    centerX             x coordinate for the center of rotation. For variation, use varIndexBase + 1.
3534       -- FWORD    centerY             y coordinate for the center of rotation. For variation, use varIndexBase + 2.
3535       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3536       [26] = function(f,format,offset)
3537           return {
3538               format  = format,
3539               name    = "PaintRotate",
3540               paint   = getpaintoffset(f,offset),
3541               centerx = readfword(f),
3542               centery = readfword(f),
3543           }
3544       end,
3545       [27] = function(f,format,offset)
3546           return {
3547               format  = format,
3548               name    = "PaintRotate",
3549               paint   = getpaintoffset(f,offset),
3550               centerx = read2dot14(f),
3551               centery = read2dot14(f),
3552               varbase = readulong(f),
3553           }
3554       end,
3555       -- Offset24 paintOffset         Offset to a Paint subtable.
3556       -- F2DOT14  xSkewAngle          Angle of skew in the direction of the x-axis, 180° in counter-clockwise degrees per 1.0 of value. For variation, use varIndexBase + 0.
3557       -- F2DOT14  ySkewAngle          Angle of skew in the direction of the y-axis, 180° in counter-clockwise degrees per 1.0 of value. For variation, use varIndexBase + 1.
3558       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3559       [28] = function(f,format,offset)
3560           return {
3561               format = format,
3562               name   = "PaintSkew",
3563               paint  = getpaintoffset(f,offset),
3564               xangle = read2dot14(f),
3565               yangle = read2dot14(f),
3566           }
3567       end,
3568       [29] = function(f,format,offset)
3569           return {
3570               format  = format,
3571               name    = "PaintSkew",
3572               paint   = getpaintoffset(f,offset),
3573               xangle  = read2dot14(f),
3574               yangle  = read2dot14(f),
3575               varbase = readulong(f),
3576           }
3577       end,
3578       -- Offset24 paintOffset         Offset to a Paint subtable.
3579       -- F2DOT14  xSkewAngle          Angle of skew in the direction of the x-axis, 180° in counter-clockwise degrees per 1.0 of value. For variation, use varIndexBase + 0.
3580       -- F2DOT14  ySkewAngle          Angle of skew in the direction of the y-axis, 180° in counter-clockwise degrees per 1.0 of value. For variation, use varIndexBase + 1.
3581       -- FWORD    centerX             x coordinate for the center of rotation. For variation, use varIndexBase + 2.
3582       -- FWORD    centerY             y coordinate for the center of rotation. For variation, use varIndexBase + 3.
3583       -- uint32   varIndexBase        Base index into DeltaSetIndexMap.
3584       [30] = function(f,format,offset)
3585           return {
3586               format  = format,
3587               name    = "PaintSkew",
3588               paint   = getpaintoffset(f,offset),
3589               xangle  = read2dot14(f),
3590               yangle  = read2dot14(f),
3591               centerx = readfword(f),
3592               centery = readfword(f),
3593           }
3594       end,
3595       [31] = function(f,format,offset)
3596           return {
3597               format  = format,
3598               name    = "PaintSkew",
3599               paint   = getpaintoffset(f,offset),
3600               xangle  = read2dot14(f),
3601               yangle  = read2dot14(f),
3602               centerx = readfword(f),
3603               centery = readfword(f),
3604               varbase = readulong(f),
3605           }
3606       end,
3607       -- Offset24 sourcePaintOffset   Offset to a source Paint table.
3608       -- uint8    compositeMode       A CompositeMode enumeration value.
3609       -- Offset24 backdropaintOffset Offset to a backdrop Paint table.
3610       [32] = function(f,format,offset)
3611           return {
3612               format   = format,
3613               name     = "PaintComposite",
3614               source   = getpaintoffset(f,offset),
3615               mode     = readuinteger(f),
3616               backdrop = getpaintoffset(f,offset),
3617           }
3618       end,
3619    }
3620
3621    local unsupported = function()
3622        return false
3623    end
3624
3625    setmetatableindex(paintreaders,function(t,format)
3626        if format then
3627            report("unsupported colr type 2 paint format %S",format)
3628            t[format] = unsupported -- problem: we don't know what to skip, so maybe best is to quit
3629        else
3630            report("possible error reading colr type 2 paint format")
3631        end
3632        return unsupported
3633    end)
3634
3635    function readers.colr(f,fontdata,specification)
3636        local tableoffset = gotodatatable(f,fontdata,"colr",specification.glyphs)
3637        if tableoffset then
3638            local version = readushort(f)
3639            if version == 0 then
3640                -- we're okay
3641            elseif version == 1 then
3642                report("table version %a of %a is %s supported for font %s",version,"colr","partially",fontdata.filename)
3643            else
3644                report("table version %a of %a is %s supported for font %s",version,"colr","not",fontdata.filename)
3645                return
3646            end
3647            if not fontdata.tables.cpal then
3648                report("color table %a in font %a has no mandate %a table","colr",fontdata.filename,"cpal")
3649                fontdata.colorpalettes = { }
3650            end
3651            local glyphs            = fontdata.glyphs
3652            local nofglyphs         = readushort(f)
3653            local baseoffset        = readulong(f)
3654--             local layeroffset       = readulong(f)
3655layeroffset       = readulong(f)
3656            local noflayers         = readushort(f)
3657            local glyphlistoffset   = 0
3658--             local layerlistoffset   = 0
3659layerlistoffset   = 0
3660            local cliplistoffset    = 0
3661            local varindexmapoffset = 0
3662            local variationoffset   = 0
3663            if version == 1 then
3664                glyphlistoffset   = readulong(f)
3665                layerlistoffset   = readulong(f)
3666                cliplistoffset    = readulong(f)
3667                varindexmapoffset = readulong(f)
3668                variationoffset   = readulong(f)
3669            end
3670            local layerrecords = { }
3671            local maxclass     = 0
3672            -- The special value 0xFFFF is foreground (but we index from 1). It
3673            -- more looks like indices into a palette so 'class' is a better name
3674            -- than 'palette'.
3675            if layeroffset > 0 and noflayers > 0 then
3676                setposition(f,tableoffset + layeroffset)
3677                for i=1,noflayers do
3678                    local slot  = readushort(f)
3679                    local class = readushort(f)
3680                    if class < 0xFFFF then
3681                        class = class + 1
3682                        if class > maxclass then
3683                            maxclass = class
3684                        end
3685                    end
3686                    layerrecords[i] = {
3687                        slot  = slot,
3688                        class = class,
3689                    }
3690                end
3691            end
3692            fontdata.maxcolorclass = maxclass
3693            if baseoffset > 0 and nofglyphs > 0 then
3694                setposition(f,tableoffset + baseoffset)
3695                for i=0,nofglyphs-1 do
3696                    local glyphindex = readushort(f)
3697                    local firstlayer = readushort(f)
3698                    local noflayers  = readushort(f)
3699                    if noflayers > 0 then
3700                        local t = { }
3701                        local g = glyphs[glyphindex]
3702                        for i=1,noflayers do
3703                            t[i] = layerrecords[firstlayer+i]
3704                        end
3705                        g.colors = t
3706                        -- This is a catch for an emoji fonts where the base glyph has no dimensions and
3707                        -- I admit that it's bad to fix this here instead of the font. But for sure someone
3708                        -- will argue that the font is ok, as one can use ascender and descender for height
3709                        -- and depth, but in tex we want granularity and exact dimensions.
3710                        local b = g.boundingbox
3711                        if not b or (b[1] == 0 and b[2] == 0 and b[3] == 0 and b[4] == 0) then
3712                            local llx, lly, urx, ury
3713                            for i=1,noflayers do
3714                                local c = glyphs[t[i].slot]
3715                                if c then
3716                                    b = c.boundingbox
3717                                    if b then
3718                                        local b1 = b[1]
3719                                        local b2 = b[2]
3720                                        local b3 = b[3]
3721                                        local b4 = b[4]
3722                                        if not llx then
3723                                            llx = b1
3724                                            lly = b2
3725                                            urx = b3
3726                                            ury = b4
3727                                        else
3728                                            if b1 < llx then llx = b1 end
3729                                            if b2 < lly then lly = b2 end
3730                                            if b3 > urx then urx = b3 end
3731                                            if b4 > ury then ury = b4 end
3732                                        end
3733                                    end
3734                                end
3735                            end
3736                            if llx then
3737                                g.boundingbox = { llx, lly, urx, ury }
3738                            end
3739                        end
3740                    end
3741                end
3742            end
3743            if next(layerrecords) then
3744                report("table version %a of %a is %s supported for font %s",version,"colr","partially",fontdata.filename)
3745                return
3746            end
3747         -- if true then
3748         --     return
3749         -- end
3750            if layerlistoffset > 0 and glyphlistoffset > 0 then
3751                local layers = { }
3752                local paints = { }
3753layeroffset = tableoffset + layerlistoffset
3754                setposition(f,layeroffset)
3755                local layercount = readulong(f)
3756             -- layers = readcardinaltable(f,layercount,uoffset)
3757                for i=1,layercount do -- zero ?
3758                    layers[i] = readulong(f) -- offsets to painttable
3759                end
3760                --
3761                glyphoffset = tableoffset + glyphlistoffset
3762                setposition(f,glyphoffset)
3763                local glyphcount = readulong(f)
3764                for i=1,glyphcount do
3765                    -- glyph index -> paintrecord
3766                    paints[readushort(f)] = readulong(f) -- paintrecord offset (32 formats)
3767                end
3768                paintdata = setmetatableindex(function(t,k)
3769                    local p = getposition(f)
3770                    setposition(f,k)
3771                    local format = readuinteger(f)
3772                    local v = paintreaders[format](f,format,k)
3773                    setposition(f,p)
3774                    t[k] = v
3775                    return v
3776                end)
3777                linesdata  = { }
3778                affinedata = { }
3779                for i=1,layercount do -- zero ?
3780                    local o = layeroffset + layers[i]
3781                    local l = paintdata[o]
3782                    if not l then
3783                        report("color table in font %a has an invalid layer entry %i, offset %i",i,layers[i])
3784                    end
3785                    layers[i] = l
3786                end
3787-- io.savedata("e:/tmp/oeps.lua",table.serialize({ root = paintdata }))
3788-- io.savedata("e:/tmp/oeps.lua",table.serialize(layers))
3789                for k, v in next, paints do
3790                    local o = glyphoffset + v - layeroffset
3791                    if paintdata[o] then
3792                        paints[k] = o -- first paint
3793                    end
3794                end
3795                -- expand format 1
3796                for k, v in next, paints do
3797                    v = paintdata[v]
3798                    if v then
3799                        local format = v.format
3800                        if format == 1 then
3801                            -- name
3802                            local count = v.count
3803                            if count then
3804                                local index = v.index + 1
3805                                local list  = { }
3806                                v.count = nil
3807                                v.index = nil
3808                                v.list  = list
3809                                for i=1,count do
3810--                                     local o = layeroffset + layers[index+i]
3811--                                     if paintdata[o] then
3812                                    list[i] = layers[index]
3813                                    index = index + 1
3814                                end
3815                            else
3816                                -- already done
3817                            end
3818                        end
3819                    else
3820                        -- missing
3821                    end
3822                end
3823                --
3824                if variationoffset > 0 then
3825                    local offsettostore = tableoffset + variationoffset
3826                    local factors       = specification.factors
3827                    if factors then
3828                        local regions, deltas = readvariationdata(f,offsettostore,factors)
3829                        report("font %a has a colr variations, check it out",fontdata.filename)
3830                     -- inspect(regions)
3831                     -- inspect(deltas)
3832                    end
3833                end
3834                --
3835                -- It will take while before I finish this, also because there has never
3836                -- been much demand for color fonts and there is no real incentive for
3837                -- spending too much time on it.
3838                --
3839                -- todo: cliplist, varbase, affine, deltas etc
3840                --
3841                -- reindex tables, gives smaller files but optional because of tracing
3842                --
3843                for k, v in next, linesdata do
3844                    setposition(f,k)
3845                    local extend = readuinteger(f)
3846                    local count  = readushort(f)
3847                    local stops  = { }
3848                    if count then
3849                        for i=1,count do
3850                            stops[i] = {
3851                                stop     = read2dot14(f),
3852                                pallette = readushort(f),
3853                                alpha    = read2dot14(f),
3854                                varbase  = v and readulong(f) or nil,
3855                            }
3856                        end
3857                        linesdata[k] = {
3858                            extend = readuinteger(f),
3859                            stops  = stops,
3860                        }
3861                    else
3862                        report("running out of linedata in colr reading")
3863                        linesdata[k] = {
3864                            extend = 0,
3865                            stops  = stops,
3866                        }
3867                        break
3868                    end
3869                end
3870                --
3871                for k, v in next, affinedata do
3872                    setposition(f,k)
3873                    affinedata[k] = {
3874                        xx = readfixed(f),
3875                        yx = readfixed(f),
3876                        xy = readfixed(f),
3877                        yy = readfixed(f),
3878                        dx = readfixed(f),
3879                        dy = readfixed(f),
3880                    }
3881                end
3882                --
3883                local function rehash(t)
3884                    local hash = { }
3885                    local data = { }
3886                    local n     = 0
3887                    for k, v in table.sortedhash(t) do
3888                        n = n + 1
3889                        hash[k] = n
3890                        data[n] = v
3891                    end
3892                    return hash, data
3893                end
3894                --
3895                if true then
3896                    local phash, pdata = rehash(paintdata)
3897                    local lhash, ldata = rehash(linesdata)
3898                    local ahash, adata = rehash(affinedata)
3899                    for k, v in next, paintdata do
3900if not v then
3901    print("todo",k,v)
3902else
3903                        local c = v.color
3904                        if c then
3905                            v.color = lhash[c]
3906                        end
3907                        local a = v.affine
3908                        if a then
3909                            v.affine = ahash[a]
3910                        end
3911                        local p = v.paint
3912                        if p then
3913                            v.paint = phash[p]
3914                            goto done
3915                        end
3916                        local l = v.list
3917                        if l then
3918                            for i=1,#l do
3919                                l[i] = phash[l[i]]
3920                            end
3921                            goto done
3922                        end
3923                        local s = v.source
3924                        if s then
3925                            v.source   = phash[s]
3926                            v.backdrop = phash[v.backdrop]
3927                         -- goto done
3928                        end
3929end
3930                      ::done::
3931                    end
3932                    paintdata = pdata
3933                    linesdata = ldata
3934                    for k, v in next, paints do -- zero indexed
3935                        paints[k] = phash[v]
3936                    end
3937                end
3938                --
3939                if not next(layerrecords) then
3940                    for k, v in next, paints do
3941                        local paint  = paintdata[v]
3942                        local format = paint.format
3943                        if format == 1 then
3944                            local list  = paint.list
3945                            local done  = { }
3946                            local count = 0
3947                            for i=1,#list do
3948                                local p = paintdata[list[i]]
3949                                local f = p.format
3950                                if f == 10 or f == 11 then
3951                                    count = count + 1
3952                                    done[count] = {
3953                                        slot  = p.glyph,
3954                                        class = i,
3955                                    }
3956                                else
3957                                    -- print(f)
3958                                    -- missing
3959                                end
3960                            end
3961                            glyphs[k].colors = done
3962                        end
3963                    end
3964                end
3965--                 fontdata.colorpaintdata  = paintdata
3966--                 fontdata.colorpaintlist  = paints
3967--                 fontdata.colorlinesdata  = linesdata
3968--                 fontdata.coloraffinedata = affinedata
3969            end
3970        end
3971      ::done::
3972        fontdata.hascolor = true
3973    end
3974
3975end
3976
3977function readers.cpal(f,fontdata,specification)
3978    local tableoffset = gotodatatable(f,fontdata,"cpal",specification.glyphs)
3979    if tableoffset then
3980        local version = readushort(f)
3981     -- if version > 1 then
3982     --     report("table version %a of %a is not supported (yet), maybe font %s is bad",version,"cpal",fontdata.filename)
3983     --     return
3984     -- end
3985        local nofpaletteentries  = readushort(f)
3986        local nofpalettes        = readushort(f)
3987        local nofcolorrecords    = readushort(f)
3988        local firstcoloroffset   = readulong(f)
3989        local colorrecords       = { }
3990        local palettes           = readcardinaltable(f,nofpalettes,ushort)
3991        if version == 1 then
3992            -- used for guis
3993            local palettettypesoffset = readulong(f)
3994            local palettelabelsoffset = readulong(f)
3995            local paletteentryoffset  = readulong(f)
3996        end
3997        setposition(f,tableoffset+firstcoloroffset)
3998        for i=1,nofcolorrecords do
3999            local b, g, r, a = readbytes(f,4)
4000            colorrecords[i] = {
4001                r, g, b, a ~= 255 and a or nil,
4002            }
4003        end
4004        for i=1,nofpalettes do
4005            local p = { }
4006            local o = palettes[i]
4007            for j=1,nofpaletteentries do
4008                p[j] = colorrecords[o+j]
4009            end
4010            palettes[i] = p
4011        end
4012        fontdata.colorpalettes = palettes
4013    end
4014end
4015
4016local compress   = gzip and gzip.compress
4017local compressed = compress and gzip.compressed
4018
4019-- At some point I will delay loading and only store the offsets.
4020
4021-- compressed = false
4022
4023function readers.svg(f,fontdata,specification)
4024    local tableoffset = gotodatatable(f,fontdata,"svg",specification.glyphs)
4025    if tableoffset then
4026        local version = readushort(f)
4027     -- if version ~= 0 then
4028     --     report("table version %a of %a is not supported (yet), maybe font %s is bad",version,"svg",fontdata.filename)
4029     --     return
4030     -- end
4031        local glyphs      = fontdata.glyphs
4032        local indexoffset = tableoffset + readulong(f)
4033        local reserved    = readulong(f)
4034        setposition(f,indexoffset)
4035        local nofentries  = readushort(f)
4036        local entries     = { }
4037        for i=1,nofentries do
4038            entries[i] = {
4039                first  = readushort(f),
4040                last   = readushort(f),
4041                offset = indexoffset + readulong(f),
4042                length = readulong(f),
4043            }
4044        end
4045        for i=1,nofentries do
4046            local entry = entries[i]
4047            setposition(f,entry.offset)
4048            local data = readstring(f,entry.length)
4049            if compressed and not compressed(data) then
4050                data = compress(data)
4051            end
4052            entries[i] = {
4053                first = entry.first,
4054                last  = entry.last,
4055                data  = data
4056            }
4057        end
4058        fontdata.svgshapes = entries
4059    end
4060    fontdata.hascolor = true
4061end
4062
4063function readers.sbix(f,fontdata,specification)
4064    local tableoffset = gotodatatable(f,fontdata,"sbix",specification.glyphs)
4065    if tableoffset then
4066        local version    = readushort(f)
4067        local flags      = readushort(f)
4068        local nofstrikes = readulong(f)
4069        local strikes    = { }
4070        local nofglyphs  = fontdata.nofglyphs
4071        for i=1,nofstrikes do
4072            strikes[i] = readulong(f)
4073        end
4074        local shapes = { }
4075        local done   = 0
4076        for i=1,nofstrikes do
4077            local strikeoffset = strikes[i] + tableoffset
4078            setposition(f,strikeoffset)
4079            strikes[i] = {
4080                ppem   = readushort(f),
4081                ppi    = readushort(f),
4082                offset = strikeoffset
4083            }
4084        end
4085        -- highest first
4086        sort(strikes,function(a,b)
4087            if b.ppem == a.ppem then
4088                return b.ppi < a.ppi
4089            else
4090                return b.ppem < a.ppem
4091            end
4092        end)
4093        local glyphs  = { }
4094     -- local delayed = fonts.handlers.typethree
4095        for i=1,nofstrikes do
4096            local strike       = strikes[i]
4097            local strikeppem   = strike.ppem
4098            local strikeppi    = strike.ppi
4099            local strikeoffset = strike.offset
4100            setposition(f,strikeoffset)
4101            for i=0,nofglyphs do
4102                glyphs[i] = readulong(f)
4103            end
4104            local glyphoffset = glyphs[0]
4105            for i=0,nofglyphs-1 do
4106                local nextoffset = glyphs[i+1]
4107                if not shapes[i] then
4108                    local datasize = nextoffset - glyphoffset
4109                    if datasize > 0 then
4110                        setposition(f,strikeoffset + glyphoffset)
4111                        local x      = readshort(f)
4112                        local y      = readshort(f)
4113                        local tag    = readtag(f) -- or just skip, we never needed it till now
4114                        local size   = datasize - 8
4115                        local data   = nil
4116                        local offset = nil
4117                     -- if delayed then
4118                            offset = getposition(f)
4119                     -- else
4120                     --     data   = readstring(f,size)
4121                     --     size   = nil
4122                     -- end
4123                        shapes[i] = {
4124                            x    = x,
4125                            y    = y,
4126                            o    = offset,
4127                            s    = size,
4128                            data = data,
4129                         -- tag  = tag, -- maybe for tracing
4130                         -- ppem = strikeppem, -- not used, for tracing
4131                         -- ppi  = strikeppi,  -- not used, for tracing
4132                        }
4133                        done = done + 1
4134                        if done == nofglyphs then
4135                            break
4136                        end
4137                    end
4138                end
4139                glyphoffset = nextoffset
4140            end
4141        end
4142        fontdata.pngshapes = shapes
4143    end
4144end
4145
4146-- Another bitmap (so not that useful) format. But Luigi found a font that
4147-- has them , so ...
4148
4149do
4150
4151    local function getmetrics(f)
4152        return {
4153            ascender              = readinteger(f),
4154            descender             = readinteger(f),
4155            widthmax              = readuinteger(f),
4156            caretslopedumerator   = readinteger(f),
4157            caretslopedenominator = readinteger(f),
4158            caretoffset           = readinteger(f),
4159            minorigin             = readinteger(f),
4160            minadvance            = readinteger(f),
4161            maxbefore             = readinteger(f),
4162            minafter              = readinteger(f),
4163            pad1                  = readinteger(f),
4164            pad2                  = readinteger(f),
4165        }
4166    end
4167
4168    -- bad names
4169
4170    local function getbigmetrics(f)
4171        -- bigmetrics, maybe just skip 9 bytes
4172        return {
4173            height       = readuinteger(f),
4174            width        = readuinteger(f),
4175            horiBearingX = readinteger(f),
4176            horiBearingY = readinteger(f),
4177            horiAdvance  = readuinteger(f),
4178            vertBearingX = readinteger(f),
4179            vertBearingY = readinteger(f),
4180            vertAdvance  = readuinteger(f),
4181        }
4182    end
4183
4184    local function getsmallmetrics(f)
4185        -- smallmetrics, maybe just skip 5 bytes
4186        return {
4187            height   = readuinteger(f),
4188            width    = readuinteger(f),
4189            bearingX = readinteger(f),
4190            bearingY = readinteger(f),
4191            advance  = readuinteger(f),
4192        }
4193    end
4194
4195    function readers.cblc(f,fontdata,specification)
4196        -- should we delay this ?
4197        local ctdttableoffset = gotodatatable(f,fontdata,"cbdt",specification.glyphs)
4198        if not ctdttableoffset then
4199            return
4200        end
4201        local cblctableoffset = gotodatatable(f,fontdata,"cblc",specification.glyphs)
4202        if cblctableoffset then
4203            local majorversion  = readushort(f)
4204            local minorversion  = readushort(f)
4205            local nofsizetables = readulong(f)
4206            local sizetables    = { }
4207            local shapes        = { }
4208            local subtables     = { }
4209            for i=1,nofsizetables do
4210                sizetables[i] = {
4211                    subtables    = readulong(f),
4212                    indexsize    = readulong(f),
4213                    nofsubtables = readulong(f),
4214                    colorref     = readulong(f),
4215                    hormetrics   = getmetrics(f),
4216                    vermetrics   = getmetrics(f),
4217                    firstindex   = readushort(f),
4218                    lastindex    = readushort(f),
4219                    ppemx        = readbyte(f),
4220                    ppemy        = readbyte(f),
4221                    bitdepth     = readbyte(f),
4222                    flags        = readbyte(f),
4223                }
4224            end
4225            sort(sizetables,function(a,b)
4226                if b.ppemx == a.ppemx then
4227                    return b.bitdepth < a.bitdepth
4228                else
4229                    return b.ppemx < a.ppemx
4230                end
4231            end)
4232            for i=1,nofsizetables do
4233                local s = sizetables[i]
4234                local d = false
4235                for j=s.firstindex,s.lastindex do
4236                    if not shapes[j] then
4237                        shapes[j] = i
4238                        d = true
4239                    end
4240                end
4241                if d then
4242                    s.used = true
4243                end
4244            end
4245            for i=1,nofsizetables do
4246                local s = sizetables[i]
4247                if s.used then
4248                    local offset = s.subtables
4249                    setposition(f,cblctableoffset+offset)
4250                    for j=1,s.nofsubtables do
4251                        local firstindex  = readushort(f)
4252                        local lastindex   = readushort(f)
4253                        local tableoffset = readulong(f) + offset
4254                        for k=firstindex,lastindex do
4255                            if shapes[k] == i then
4256                                local s = subtables[tableoffset]
4257                                if not s then
4258                                    s = {
4259                                        firstindex = firstindex,
4260                                        lastindex  = lastindex,
4261                                    }
4262                                    subtables[tableoffset] = s
4263                                end
4264                                shapes[k] = s
4265                            end
4266                        end
4267                    end
4268                end
4269            end
4270
4271            -- there is no need to sort in string stream but we have a nicer trace
4272            -- if needed
4273
4274            for offset, subtable in sortedhash(subtables) do
4275                local tabletype  = readushort(f)
4276                subtable.format  = readushort(f)
4277                local baseoffset = readulong(f) + ctdttableoffset
4278                local offsets    = { }
4279                local metrics    = nil
4280                if tabletype == 1 then
4281                    -- we have the usual one more to get the size
4282                    for i=subtable.firstindex,subtable.lastindex do
4283                        offsets[i] = readulong(f) + baseoffset
4284                    end
4285                    skipbytes(f,4)
4286                elseif tabletype == 2 then
4287                    local size = readulong(f)
4288                    local done = baseoffset
4289                    metrics = getbigmetrics(f)
4290                    for i=subtable.firstindex,subtable.lastindex do
4291                        offsets[i] = done
4292                        done = done + size
4293                    end
4294                elseif tabletype == 3 then
4295                    -- we have the usual one more to get the size
4296                    local n = subtable.lastindex - subtable.firstindex + 2
4297                    for i=subtable.firstindex,subtable.lastindex do
4298                        offsets[i] = readushort(f) + baseoffset
4299                    end
4300                    if math.odd(n) then
4301                        skipbytes(f,4)
4302                    else
4303                        skipbytes(f,2)
4304                    end
4305                elseif tabletype == 4 then
4306                    for i=1,readulong(f) do
4307                        offsets[readushort(f)] = readushort(f) + baseoffset
4308                    end
4309                elseif tabletype == 5 then
4310                    local size = readulong(f)
4311                    local done = baseoffset
4312                    metrics = getbigmetrics(f)
4313                    local n = readulong(f)
4314                    for i=1,n do
4315                        offsets[readushort(f)] = done
4316                        done = done + size
4317                    end
4318                    if math.odd(n) then
4319                        skipbytes(f,2)
4320                    end
4321                else
4322                    return -- unsupported format
4323                end
4324                subtable.offsets = offsets
4325                subtable.metrics = metrics
4326            end
4327
4328            -- we only support a few sensible types ... there are hardly any fonts so
4329            -- why are there so many variants ... not the best spec
4330
4331            local default = { width = 0, height = 0 }
4332            local glyphs  = fontdata.glyphs
4333         -- local delayed = fonts.handlers.typethree
4334
4335            for index, subtable in sortedhash(shapes) do
4336                if type(subtable) == "table" then
4337                    local data    = nil
4338                    local size    = nil
4339                    local metrics = default
4340                    local format  = subtable.format
4341                    local offset  = subtable.offsets[index]
4342                    setposition(f,offset)
4343                    if format == 17 then
4344                        metrics = getsmallmetrics(f)
4345                        size    = true
4346                    elseif format == 18 then
4347                        metrics = getbigmetrics(f)
4348                        size    = true
4349                    elseif format == 19 then
4350                        metrics = subtable.metrics
4351                        size    = true
4352                    else
4353                        -- forget about it
4354                    end
4355                    if size then
4356                        size = readulong(f)
4357                     -- if delayed then
4358                            offset = getposition(f)
4359                            data   = nil
4360                     -- else
4361                     --     offset = nil
4362                     --     data   = readstring(f,size)
4363                     --     size   = nil
4364                     -- end
4365                    else
4366                        offset = nil
4367                    end
4368                    local x = metrics.width
4369                    local y = metrics.height
4370                    shapes[index] = {
4371                        x    = x,
4372                        y    = y,
4373                        o    = offset,
4374                        s    = size,
4375                        data = data,
4376                    }
4377                    -- I'll look into this in more details when needed
4378                    -- as we can use the bearings to get better boxes.
4379                    local glyph = glyphs[index]
4380                    if not glyph.boundingbox then
4381                        local width  = glyph.width
4382                        local height = width * y/x
4383                        glyph.boundingbox = { 0, 0, width, height }
4384                    end
4385                else
4386                    shapes[index] = {
4387                        x    = 0,
4388                        y    = 0,
4389                        data = "", -- or just nil
4390                    }
4391                end
4392            end
4393
4394            fontdata.pngshapes = shapes -- we cheat
4395        end
4396    end
4397
4398    function readers.cbdt(f,fontdata,specification)
4399     -- local tableoffset = gotodatatable(f,fontdata,"ctdt",specification.glyphs)
4400     -- if tableoffset then
4401     --     local majorversion = readushort(f)
4402     --     local minorversion = readushort(f)
4403     -- end
4404    end
4405
4406    -- function readers.ebdt(f,fontdata,specification)
4407    --     if specification.glyphs then
4408    --     end
4409    -- end
4410
4411    -- function readers.ebsc(f,fontdata,specification)
4412    --     if specification.glyphs then
4413    --     end
4414    -- end
4415
4416    -- function readers.eblc(f,fontdata,specification)
4417    --     if specification.glyphs then
4418    --     end
4419    -- end
4420
4421end
4422
4423-- + AVAR : optional
4424-- + CFF2 : otf outlines
4425-- - CVAR : ttf hinting, not needed
4426-- + FVAR : the variations
4427-- + GVAR : ttf outline changes
4428-- + HVAR : horizontal changes
4429-- + MVAR : metric changes
4430-- + STAT : relations within fonts
4431-- * VVAR : vertical changes
4432--
4433-- * BASE : extra baseline adjustments
4434-- - GASP : not needed
4435-- + GDEF : not needed (carets)
4436-- + GPOS : adapted device tables (needed?)
4437-- + GSUB : new table
4438-- + NAME : 25 added
4439
4440function readers.stat(f,fontdata,specification)
4441    local tableoffset = gotodatatable(f,fontdata,"stat",true) -- specification.variable
4442    if tableoffset then
4443        local extras       = fontdata.extras
4444        local version      = readulong(f) -- 0x00010000
4445        local axissize     = readushort(f)
4446        local nofaxis      = readushort(f)
4447        local axisoffset   = readulong(f)
4448        local nofvalues    = readushort(f)
4449        local valuesoffset = readulong(f)
4450        local fallbackname = extras[readushort(f)] -- beta fonts mess up
4451        local axis         = { }
4452        local values       = { }
4453        setposition(f,tableoffset+axisoffset)
4454        for i=1,nofaxis do
4455            local tag = readtag(f)
4456            axis[i] = {
4457                tag      = tag,
4458                name     = lower(extras[readushort(f)] or tag),
4459                ordering = readushort(f), -- maybe gaps
4460                variants = { }
4461            }
4462        end
4463        -- flags:
4464        --
4465        -- 0x0001 : OlderSiblingFontAttribute
4466        -- 0x0002 : ElidableAxisValueName
4467        -- 0xFFFC : reservedFlags
4468        --
4469        setposition(f,tableoffset+valuesoffset)
4470        for i=1,nofvalues do
4471            values[i] = readushort(f)
4472        end
4473        for i=1,nofvalues do
4474            setposition(f,tableoffset + valuesoffset + values[i])
4475            local format  = readushort(f)
4476            local index   = readushort(f) + 1
4477            local flags   = readushort(f)
4478            local name    = lower(extras[readushort(f)] or "no name")
4479            local value   = readfixed(f)
4480            local variant
4481            if format == 1 then
4482                variant = {
4483                    flags = flags,
4484                    name  = name,
4485                    value = value,
4486                }
4487            elseif format == 2 then
4488                variant = {
4489                    flags   = flags,
4490                    name    = name,
4491                    value   = value,
4492                    minimum = readfixed(f),
4493                    maximum = readfixed(f),
4494                }
4495            elseif format == 3 then
4496                variant = {
4497                    flags = flags,
4498                    name  = name,
4499                    value = value,
4500                    link  = readfixed(f),
4501                }
4502            end
4503            insert(axis[index].variants,variant)
4504        end
4505        sort(axis,function(a,b)
4506            return a.ordering < b.ordering
4507        end)
4508        for i=1,#axis do
4509            local a = axis[i]
4510            sort(a.variants,function(a,b)
4511                return a.name < b.name
4512            end)
4513            a.ordering = nil
4514        end
4515        setvariabledata(fontdata,"designaxis",axis)
4516        setvariabledata(fontdata,"fallbackname",fallbackname)
4517    end
4518end
4519
4520-- The avar table is optional and used in combination with fvar. Given the
4521-- detailed explanation about bad values we expect the worst and do some
4522-- checking.
4523
4524function readers.avar(f,fontdata,specification)
4525    local tableoffset = gotodatatable(f,fontdata,"avar",true) -- specification.variable
4526    if tableoffset then
4527
4528        local function collect()
4529            local nofvalues = readushort(f)
4530            local values    = { }
4531            local lastfrom  = false
4532            local lastto    = false
4533            for i=1,nofvalues do
4534                local from = read2dot14(f)
4535                local to   = read2dot14(f)
4536                if lastfrom and from <= lastfrom then
4537                    -- ignore
4538                elseif lastto and to >= lastto then
4539                    -- ignore
4540                else
4541                    values[#values+1] = { from, to }
4542                    lastfrom, lastto = from, to
4543                end
4544            end
4545            nofvalues = #values
4546            if nofvalues > 2 then
4547                local some = values[1]
4548                if some[1] == -1 and some[2] == -1 then
4549                    some = values[nofvalues]
4550                    if some[1] == 1 and some[2] == 1 then
4551                        for i=2,nofvalues-1 do
4552                            some = values[i]
4553                            if some[1] == 0 and some[2] == 0 then
4554                                return values
4555                            end
4556                        end
4557                    end
4558                end
4559            end
4560            return false
4561        end
4562
4563        local version  = readulong(f) -- 0x00010000
4564        local reserved = readushort(f)
4565        local nofaxis  = readushort(f)
4566        local segments = { }
4567        for i=1,nofaxis do
4568            segments[i] = collect()
4569        end
4570        setvariabledata(fontdata,"segments",segments)
4571    end
4572end
4573
4574function readers.fvar(f,fontdata,specification)
4575    local tableoffset = gotodatatable(f,fontdata,"fvar",true) -- specification.variable or specification.instancenames
4576    if tableoffset then
4577        local version         = readulong(f) -- 0x00010000
4578        local offsettoaxis    = tableoffset + readushort(f)
4579        local reserved        = skipshort(f)
4580        -- pair 1
4581        local nofaxis         = readushort(f)
4582        local sizeofaxis      = readushort(f)
4583        -- pair 2
4584        local nofinstances    = readushort(f)
4585        local sizeofinstances = readushort(f)
4586        --
4587        local extras    = fontdata.extras
4588        local axis      = { }
4589        local instances = { }
4590        --
4591        setposition(f,offsettoaxis)
4592        --
4593        for i=1,nofaxis do
4594            axis[i] = {
4595                tag     = readtag(f),   -- ital opsz slnt wdth wght
4596                minimum = readfixed(f),
4597                default = readfixed(f),
4598                maximum = readfixed(f),
4599                flags   = readushort(f),
4600                name    = lower(extras[readushort(f)] or "bad name"),
4601            }
4602            local n = sizeofaxis - 20
4603            if n > 0 then
4604                skipbytes(f,n)
4605            elseif n < 0 then
4606                -- error
4607            end
4608        end
4609        --
4610        local nofbytes   = 2 + 2 + 2 + nofaxis * 4
4611        local readpsname = nofbytes <= sizeofinstances
4612        local skippable  = sizeofinstances - nofbytes
4613        for i=1,nofinstances do
4614            local subfamid = readushort(f)
4615            local flags    = readushort(f) -- 0, not used yet
4616            local values   = { }
4617            for i=1,nofaxis do
4618                values[i] = {
4619                    axis  = axis[i].tag,
4620                    value = readfixed(f),
4621                }
4622            end
4623            local psnameid = readpsname and readushort(f) or 0xFFFF
4624            if subfamid == 2 or subfamid == 17 then
4625                -- okay
4626            elseif subfamid == 0xFFFF then
4627                subfamid = nil
4628            elseif subfamid <= 256 or subfamid >= 32768 then
4629                subfamid = nil -- actually an error
4630            end
4631            if psnameid == 6 then
4632                -- okay
4633            elseif psnameid == 0xFFFF then
4634                psnameid = nil
4635            elseif psnameid <= 256 or psnameid >= 32768 then
4636                psnameid = nil -- actually an error
4637            end
4638            instances[i] = {
4639             -- flags     = flags,
4640                subfamily = extras[subfamid],
4641                psname    = psnameid and extras[psnameid] or nil,
4642                values    = values,
4643            }
4644            if skippable > 0 then
4645                skipbytes(f,skippable)
4646            end
4647        end
4648        setvariabledata(fontdata,"axis",axis)
4649        setvariabledata(fontdata,"instances",instances)
4650    end
4651end
4652
4653local function calculate(f,fontdata,specification,offset,field,regions,deltas,nozero)
4654    --
4655    -- innerIndexBitCountMask = 0x000F
4656    -- mapEntrySizeMask       = 0x0030
4657    -- reservedFlags          = 0xFFC0
4658    --
4659    -- outerIndex = entry >>       ((entryFormat & innerIndexBitCountMask) + 1)
4660    -- innerIndex = entry & ((1 << ((entryFormat & innerIndexBitCountMask) + 1)) - 1)
4661    --
4662    setposition(f,offset)
4663    local format       = readushort(f) -- todo: check
4664    local mapcount     = readushort(f)
4665 -- local entrysize    = rshift(band(format,0x0030),4) + 1
4666    local entrysize    = (((format & 0x0030) >> 4) & 0xFFFFFFFF) + 1
4667    local nofinnerbits = (format & 0x000F) + 1 -- n of inner bits
4668 -- local innermask    = lshift(1,nofinnerbits) - 1
4669    local innermask    = (1 << nofinnerbits) - 1
4670    local readcardinal = read_cardinal[entrysize] -- 1 upto 4 bytes
4671    local innerindex   = { } -- size is mapcount
4672    local outerindex   = { } -- size is mapcount
4673    for i=0,mapcount-1 do
4674        local mapdata = readcardinal(f)
4675     -- outerindex[i] = rshift(mapdata,nofinnerbits)
4676        outerindex[i] = (mapdata >> nofinnerbits) & 0xFFFFFFFF
4677        innerindex[i] = (mapdata & innermask)
4678    end
4679    -- use last entry when no match i
4680    setvariabledata(fontdata,"hvarwidths",true)
4681    local glyphs = fontdata.glyphs
4682    for i=0,fontdata.nofglyphs-1 do
4683        local glyph = glyphs[i]
4684        local outer = outerindex[i] or 0
4685        local inner = innerindex[i] or i
4686        if outer and inner then -- not needed
4687            local delta = deltas[outer+1]
4688            if delta then
4689                local d = delta.deltas[inner+1]
4690                if d then
4691                    local scales = delta.scales
4692                    local deltaw = field and glyph[field] or 0
4693                    for i=1,#scales do
4694                        local di = d[i]
4695                        if di then
4696                            deltaw = deltaw + scales[i] * di
4697                        else
4698                            break -- can't happen
4699                        end
4700                    end
4701                    deltaw = round(deltaw)
4702                    if nozero and deltaw == 0 then
4703                        -- no need for dlsb zero
4704                    else
4705                        glyph[field] = deltaw
4706                    end
4707                end
4708            end
4709        end
4710    end
4711end
4712
4713-- Todo: when it's tested for a while the lsb hackery can be backported from the
4714-- font-dsp.lmt file.
4715
4716function readers.hvar(f,fontdata,specification)
4717    local factors = specification.factors
4718    if not factors then
4719        return
4720    end
4721    local tableoffset = gotodatatable(f,fontdata,"hvar",specification.variable)
4722    if not tableoffset then
4723     -- report("no hvar table, expect problems due to messy widths")
4724        return
4725    end
4726    local version         = readulong(f) -- 0x00010000
4727    local variationoffset = tableoffset + readulong(f) -- the store
4728    local advanceoffset   = tableoffset + readulong(f)
4729    local lsboffset       = tableoffset + readulong(f)
4730    local rsboffset       = tableoffset + readulong(f)
4731    if variationoffset > tableoffset then
4732        local regions, deltas = readvariationdata(f,variationoffset,factors)
4733        if regions then
4734            if advanceoffset > tableoffset then
4735                calculate(f,fontdata,specification,advanceoffset,"width",regions,deltas,false)
4736            end
4737            -- I don't want to save the lsb as it is the llx that we already store but as
4738            -- we're ahead of reading the bounding box so we cannot set the right lsb here
4739            -- so we set the delta (d) instead.
4740            if lsboffset > tableoffset then
4741                calculate(f,fontdata,specification,lsboffset,"dlsb",regions,deltas,true) -- delta lsb
4742            end
4743         -- if rsboffset > tableoffset then
4744         --     -- we don't use right side bearings
4745         -- end
4746         -- setvariabledata(fontdata,"hregions",regions)
4747        end
4748
4749    end
4750
4751end
4752
4753function readers.vvar(f,fontdata,specification)
4754    if not specification.variable then
4755        return
4756    end
4757end
4758
4759function readers.mvar(f,fontdata,specification)
4760    local tableoffset = gotodatatable(f,fontdata,"mvar",specification.variable)
4761    if tableoffset then
4762        local version       = readulong(f) -- 0x00010000
4763        local reserved      = skipshort(f,1)
4764        local recordsize    = readushort(f)
4765        local nofrecords    = readushort(f)
4766        local offsettostore = tableoffset + readushort(f)
4767        local dimensions    = { }
4768        local factors       = specification.factors
4769        if factors then
4770            local regions, deltas = readvariationdata(f,offsettostore,factors)
4771            for i=1,nofrecords do
4772                local tag = readtag(f)
4773                local var = variabletags[tag]
4774                if var then
4775                    local outer = readushort(f)
4776                    local inner = readushort(f)
4777                    local delta = deltas[outer+1]
4778                    if delta then
4779                        local d = delta.deltas[inner+1]
4780                        if d then
4781                            local scales = delta.scales
4782                            local dd = 0
4783                            for i=1,#scales do
4784                                dd = dd + scales[i] * d[i]
4785                            end
4786                            var(fontdata,round(dd))
4787                        end
4788                    end
4789                else
4790                    skipshort(f,2)
4791                end
4792                if recordsize > 8 then -- 4 + 2 + 2
4793                    skipbytes(recordsize-8)
4794                end
4795            end
4796        end
4797     -- setvariabledata(fontdata,"mregions",regions)
4798    end
4799end
4800
4801function readers.dsig(f,fontdata,specification)
4802    -- We're not going to deal with this security crap.
4803end
4804