font-tpk.lmt /size: 51 Kb    last modification: 2024-01-16 10:22
1if not modules then modules = { } end modules ['font-tpk'] = {
2    version   = 1.001,
3    optimize  = true,
4    comment   = "companion to font-lib.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-- The bitmap loader is more or less derived from the luatex version (taco)
11-- which is derived from pdftex (thanh) who uses code from dvips (thomas)
12-- adapted by piet ... etc. The tfm and vf readers are also derived from
13-- luatex. All do things a bit more luaish and errors are of course mine.
14
15local next = next
16----- extract, band, lshift, rshift = bit32.extract, bit32.band, bit32.lshift, bit32.rshift
17----- idiv = number.idiv
18local char = string.char
19local concat, insert, remove, copy = table.concat, table.insert, table.remove, table.copy
20local tobitstring = number.tobitstring
21local formatters = string.formatters
22local round = math.round
23local addsuffix, basename, nameonly, pathpart, joinfile = file.addsuffix, file.basename, file.nameonly, file.pathpart, file.join
24
25local findbinfile   = resolvers.findbinfile
26
27local streams       = utilities.streams
28local openstream    = streams.open
29local streamsize    = streams.size
30local readcardinal1 = streams.readcardinal1
31local readcardinal2 = streams.readcardinal2
32local readcardinal3 = streams.readcardinal3
33local readcardinal4 = streams.readcardinal4
34local readinteger1  = streams.readinteger1
35local readinteger2  = streams.readinteger2
36local readinteger3  = streams.readinteger3
37local readinteger4  = streams.readinteger4
38local readbyte      = streams.readbyte
39local readbytes     = streams.readbytes
40local readstring    = streams.readstring
41local skipbytes     = streams.skipbytes
42local getposition   = streams.getposition
43local setposition   = streams.setposition
44
45if not fonts then fonts = { handlers = { tfm = { } } } end
46
47local handlers = fonts.handlers
48local tfm      = handlers.tfm or { }
49handlers.tfm   = tfm
50tfm.version    = 1.007
51
52local readers  = tfm.readers or { }
53tfm.readers    = readers
54
55-- Performance is no real issue here so I didn't optimize too much. After
56-- all, these files are small and we mostly use opentype or type1 fonts.
57
58
59do
60
61    local function readbitmap(glyph,s,flagbyte)
62
63        local inputbyte   = 0
64        local bitweight   = 0
65        local dynf        = 0
66        local remainder   = 0
67        local realfunc    = nil
68        local repeatcount = 0
69
70        local function getnyb() -- can be inlined
71            if bitweight == 0 then
72                bitweight = 16
73                inputbyte = readbyte(s)
74             -- return extract(inputbyte,4,4)
75                return (inputbyte >> 4) & 0xF -- no need for & 0xF
76            else
77                bitweight = 0
78                return inputbyte & 15
79            end
80        end
81
82        local function getbit() -- can be inlined
83         -- bitweight = rshift(bitweight,1)
84            bitweight = (bitweight >> 1) & 0xFFFFFFFF -- no need for &
85            if bitweight == 0 then -- actually we can check for 1
86                inputbyte = readbyte(s)
87                bitweight = 128
88            end
89            return inputbyte & bitweight
90        end
91
92        local rest, handlehuge, pkpackednum
93
94        rest = function()
95            if remainder < 0 then
96                remainder = -remainder
97                return 0
98            elseif remainder > 4000 then
99                remainder = 4000 - remainder
100                return 4000
101            elseif remainder > 0 then
102                local i = remainder
103                remainder = 0
104                realfunc  = pkpackednum
105                return i
106            else
107             -- error = "pk issue that shouldn't happen"
108                return 0
109            end
110        end
111
112        handlehuge = function (i,j)
113            while i ~= 0 do
114             -- j = lshift(j,4) + getnyb()
115                j = ((j << 4) & 0xFFFFFFFF) + getnyb() -- no need for &
116                i = i - 1
117            end
118            remainder = j - 15 + (13 - dynf) * 16 + dynf
119            realfunc  = rest
120            return rest()
121        end
122
123        pkpackednum = function()
124            local i = getnyb(s)
125            if i == 0 then
126                repeat
127                    j = getnyb()
128                    i = i + 1
129                until (j ~= 0)
130                if i > 3 then
131                    return handlehuge(i,j)
132                else
133                    for i=1,i do
134                        j = j * 16 + getnyb()
135                    end
136                    return j - 15 + (13 - dynf) * 16 + dynf
137                end
138            elseif i <= dynf then
139                return i
140            elseif i < 14 then
141                return (i - dynf - 1) * 16 + getnyb() + dynf + 1
142            elseif i == 14 then
143                repeatcount = pkpackednum()
144            else
145                repeatcount = 1
146            end
147            return realfunc()
148        end
149
150        local gpower = { [0] =
151                0,   1,    3,    7,   15,   31,    63,   127,
152              255, 511, 1023, 2047, 4095, 8191, 16383, 32767,
153            65535
154        }
155
156        local raster = { }
157        local r      = 0
158        glyph.stream = raster
159
160        local xsize      = glyph.xsize
161        local ysize      = glyph.ysize
162        local word       = 0
163        local wordweight = 0
164        local wordwidth  = (xsize + 15) // 16
165        local rowsleft   = 0
166        local turnon     = (flagbyte & 8) == 8 and true or false
167        local hbit       = 0
168        local count      = 0
169        --
170        realfunc         = pkpackednum
171        dynf             = flagbyte // 16
172        --
173        if dynf == 14 then
174            bitweight = 0
175            for i=1,ysize do
176                word       = 0
177                wordweight = 32768
178                for j=1,xsize do
179                    if getbit() ~= 0 then
180                        word = word + wordweight
181                    end
182                 -- wordweight = rshift(wordweight,1)
183                    wordweight = (wordweight >> 1) & 0xFFFFFFFF -- no need for &
184                    if wordweight == 0 then
185                        r          = r + 1
186                        raster[r]  = word
187                        word       = 0
188                        wordweight = 32768
189                    end
190                end
191                if wordweight ~= 32768 then
192                    r         = r + 1
193                    raster[r] = word
194                end
195            end
196        else
197            rowsleft    = ysize
198            hbit        = xsize
199            repeatcount = 0
200            wordweight  = 16
201            word        = 0
202            bitweight   = 0
203            while rowsleft > 0 do
204                count = realfunc()
205                while count ~= 0 do
206                    if count < wordweight and count < hbit then
207                        if turnon then
208                            word = word + gpower[wordweight] - gpower[wordweight - count]
209                        end
210                        hbit       = hbit - count
211                        wordweight = wordweight - count
212                        count      = 0
213                    elseif count >= hbit and hbit <= wordweight then
214                        if turnon then
215                            word = word + gpower[wordweight] - gpower[wordweight - hbit]
216                        end
217                        r          = r + 1
218                        raster[r]  = word
219                        for i=1,repeatcount*wordwidth do
220                            r          = r + 1
221                            raster[r]  = raster[r - wordwidth]
222                        end
223                        rowsleft    = rowsleft - repeatcount - 1
224                        repeatcount = 0
225                        word        = 0
226                        wordweight  = 16
227                        count       = count - hbit
228                        hbit        = xsize
229                    else
230                        if turnon then
231                            word = word + gpower[wordweight]
232                        end
233                        r          = r + 1
234                        raster[r]  = word
235                        word       = 0
236                        count      = count - wordweight
237                        hbit       = hbit - wordweight
238                        wordweight = 16
239                    end
240                end
241                turnon = not turnon
242            end
243            if rowsleft ~= 0 or hbit ~= xsize then
244                print("ERROR",rowsleft,hbit,xsize)
245                -- error = "error while unpacking, more bits than required"
246            end
247        end
248
249    end
250
251    local function showpk(stream,xsize,ysize,oneline)
252        local result = { }
253        local rr     = { }
254        local r      = 0
255        local s      = 0
256        local cw     = (xsize+ 7) //  8
257        local rw     = (xsize+15) // 16
258        local extra  = 2 * rw == cw
259        local b
260        for y=1,ysize do
261            r = 0
262            for x=1,rw-1 do
263                s = s + 1 ; b = stream[s]
264                r = r + 1 ; rr[r] = tobitstring(b,16,16)
265            end
266                s = s + 1 ; b = stream[s]
267            if extra then
268                r = r + 1 ; rr[r] = tobitstring(b,16,16)
269            else
270                r = r + 1 ; rr[r] = tobitstring(b>>8,8,8)
271            end
272            result[y] = concat(rr)
273        end
274        if oneline then
275            return concat(result),ysize > 0 and #result[1]or 0,ysize
276        else
277            return concat(result,"\n")
278        end
279    end
280
281    function readers.showpk(glyph,oneline)
282        if glyph then
283            return showpk(glyph.stream,glyph.xsize,glyph.ysize,oneline)
284        end
285    end
286
287    local template = formatters [ [[
288%N 0 %i %i %i %i d1
289%i 0 0 %i %i %i cm
290BI
291  /W %i
292  /H %i
293  /IM true
294  /BPC 1
295  /D [1 0]
296ID %t
297EI]] ]
298
299    function readers.pktopdf(glyph,data,factor)
300        local width   = data.width * factor
301width = round(width)
302        local xsize   = glyph.xsize or 0
303        local ysize   = glyph.ysize or 0
304        local xoffset = glyph.xoffset or 0
305        local yoffset = glyph.yoffset or 0
306        local stream  = glyph.stream
307
308     -- local dpi     = 1
309     -- local newdpi  = 1
310     --
311     -- local xdpi    = dpi * xsize / newdpi
312     -- local ydpi    = dpi * ysize / newdpi
313
314        local llx     = - xoffset
315        local lly     = yoffset - ysize + 1
316        local urx     = llx + xsize + 1
317        local ury     = lly + ysize
318
319        local result  = { }
320        local r       = 0
321        local s       = 0
322        local cw      = (xsize+ 7) //  8
323        local rw      = (xsize+15) // 16
324        local extra   = 2 * rw == cw
325        local b
326        for y=1,ysize do
327            for x=1,rw-1 do
328                s = s + 1 ; b = stream[s]
329--               r = r + 1 ; result[r] = char(extract(b,8,8),extract(b,0,8))
330                 r = r + 1 ; result[r] = char((b >> 8) & 0xFF,b & 0xFF)
331            end
332            s = s + 1 ; b = stream[s]
333            if extra then
334--               r = r + 1 ; result[r] = char(extract(b,8,8),extract(b,0,8))
335                 r = r + 1 ; result[r] = char((b >> 8) & 0xFF,b & 0xFF)
336            else
337--               r = r + 1 ; result[r] = char(extract(b,8,8))
338                 r = r + 1 ; result[r] = char((b >> 8) & 0xFF)
339            end
340        end
341     -- return template(width,llx,lly,urx,ury,xdpi,ydpi,llx,lly,xsize,ysize,result), width
342        return template(width,llx,lly,urx,ury,xsize,ysize,llx,lly,xsize,ysize,result), width
343    end
344
345    local template = formatters [ [[
346%N 0 %N %N %N %N d1
3471 0 0 1 %N %N cm
348%t h f
349]] ]
350
351-- S
352
353    local f_curveto = formatters["%N %N %N %N %N %N c"]
354    local f_moveto  = formatters["%N %N m"]
355    local f_lineto  = formatters["%N %N l"]
356
357    function readers.potracedtopdf(glyph,data,factor,settings)
358        local width   = data.width * factor
359-- width = round(10*width/65536)
360width = round(width)
361        local xsize   = glyph.xsize or 0
362        local ysize   = glyph.ysize or 0
363        local xoffset = glyph.xoffset or 0
364        local yoffset = glyph.yoffset or 0
365        local stream  = glyph.stream
366
367        local llx     = - xoffset
368        local lly     = yoffset - ysize + 1
369        local urx     = llx + xsize + 1
370        local ury     = lly + ysize
371
372        local bytes, w, h = showpk(stream,xsize,ysize,true)
373        local result = potrace.convert(bytes,settings,w,h)
374        if result then
375            for i=1,#result do
376                local ri = result[i]
377                local ni = #ri
378                for j=1,ni do
379                    local tj = ri[j]
380                    local nj = #tj
381                    local x1 = tj[1]
382                    local y1 = tj[2]
383                    if nj == 6 then
384                        ri[j] = f_curveto(tj[3],tj[4],tj[5],tj[6],x1,y1)
385                    elseif j == 1 then
386                        ri[j] = f_moveto(x1,y1)
387                    else
388                        ri[j] = f_lineto(x1,y1)
389                    end
390                end
391                ri[ni+1] = " "
392                result[i] = concat(ri," ")
393            end
394llx = round(llx)
395lly = round(lly)
396urx = round(urx)
397ury = round(ury)
398            return template(width,llx,lly,urx,ury,llx,lly,result), width
399        end
400
401    end
402
403    function readers.loadpk(filename)
404        local s = openstream(filename)
405        if s then
406            local preamble   = readcardinal1(s)
407            local version    = readcardinal1(s)
408            local comment    = readstring(s,readcardinal1(s))
409            local designsize = readcardinal4(s)
410            local checksum   = readcardinal4(s)
411            local hppp       = readcardinal4(s)
412            local vppp       = readcardinal4(s)
413            if preamble ~= 247 or version ~= 89 or not vppp then
414                return { error = "invalid preamble" }
415            end
416            local glyphs = { }
417            local data   = {
418                designsize = designsize,
419                comment    = comment,
420                hppp       = hppp,
421                vppp       = vppp,
422                glyphs     = glyphs,
423                resolution = round(72.27*hppp/65536),
424            }
425            while true do
426                local flagbyte = readcardinal1(s)
427                if flagbyte < 240 then
428                    local c = flagbyte & 7
429                    local length, index, width, pixels, xsize, ysize, xoffset, yoffset
430                    if c >= 0 and c <= 3 then
431                        length  = (flagbyte & 7) * 256 + readcardinal1(s) - 3
432                        index   = readcardinal1(s)
433                        width   = readinteger3(s)
434                        pixels  = readcardinal1(s)
435                        xsize   = readcardinal1(s)
436                        ysize   = readcardinal1(s)
437                        xoffset = readinteger1(s)
438                        yoffset = readinteger1(s)
439                    elseif c >= 4 and c <= 6 then
440                        length  = (flagbyte & 3) * 65536 + readcardinal1(s) * 256 + readcardinal1(s) - 4
441                        index   = readcardinal1(s)
442                        width   = readinteger3(s)
443                        pixels  = readcardinal2(s)
444                        xsize   = readcardinal2(s)
445                        ysize   = readcardinal2(s)
446                        xoffset = readinteger2(s)
447                        yoffset = readinteger2(s)
448                    else -- 7
449                        length  = readcardinal4(s) - 9
450                        index   = readcardinal4(s)
451                        width   = readinteger4(s)
452                        pixels  = readcardinal4(s)
453                                  readcardinal4(s)
454                        xsize   = readcardinal4(s)
455                        ysize   = readcardinal4(s)
456                        xoffset = readinteger4(s)
457                        yoffset = readinteger4(s)
458                    end
459                    local glyph = {
460                        index   = index,
461                        width   = width,
462                        pixels  = pixels,
463                        xsize   = xsize,
464                        ysize   = ysize,
465                        xoffset = xoffset,
466                        yoffset = yoffset,
467                    }
468                    if length <= 0 then
469                        data.error = "bad packet"
470                        return data
471                    end
472                    readbitmap(glyph,s,flagbyte)
473                    glyphs[index] = glyph
474                elseif flagbyte == 240 then
475                    -- k[1] x[k]
476                    skipbytes(s,readcardinal1(s))
477                elseif flagbyte == 241 then
478                    -- k[2] x[k]
479                    skipbytes(s,readcardinal2(s)*2)
480                elseif flagbyte == 242 then
481                    -- k[3] x[k]
482                    skipbytes(s,readcardinal3(s)*3)
483                elseif flagbyte == 243 then
484                    -- k[4] x[k]
485                    skipbytes(s,readcardinal4(s)*4) -- readinteger4
486                elseif flagbyte == 244 then
487                    -- y[4]
488                    skipbytes(s,4)
489                elseif flagbyte == 245 then
490                    break
491                elseif flagbyte == 246 then
492                    -- nop
493                else
494                    data.error = "unknown pk command"
495                    break
496                end
497            end
498            return data
499        end
500    end
501
502end
503
504do
505
506    local leftboundary  = -1
507    local rightboundary = -2
508    local boundarychar  = 65536
509
510    local function toparts(extensible)
511        local top      = extensible.top      or 0
512        local middle   = extensible.middle   or 0
513        local extender = extensible.extender or 0
514        local bottom   = extensible.bottom   or 0
515        local extend   = extender ~= 0 and { glyph = extender, extender = 1 }
516        if bottom == 0 and top == 0 and middle == 0 then
517            if extend then
518                return {
519                    { glyph = extender },
520                    extend,
521                }
522            end
523        else
524            local list = { }
525            local l    = 0
526            if bottom ~= 0 then
527                l = l + 1 ; list[l] = { glyph = bottom }
528            end
529            if extend then
530                l = l + 1 ; list[l] = extend
531            end
532            if middle ~= 0 then
533                l = l + 1 ; list[l] = { glyph = middle }
534                if extend then
535                    l = l + 1 ; list[l] = extend
536                end
537            end
538            if top ~= 0 then
539                l = l + 1 ; list[l] = { glyph = top }
540            end
541            return list
542        end
543    end
544
545    -- We don't cache because we hardly load tfm files multiple times and we need
546    -- to copy them anyway.
547
548    tfm.cache = containers.define("fonts", "tfm", tfm.version, true, true) -- reload: true
549
550    local filecache = tfm.cache
551    local cleanname = fonts.handlers.otf.readers.helpers.cleanname
552
553    local caching   = true -- mainly for MS and HH as they test huge files with many instances
554
555    function readers.loadtfm(filename)
556        local data
557        --
558        local fileattr   = lfs.attributes(filename)
559        local filesize   = fileattr and fileattr.size or 0
560        local filetime   = fileattr and fileattr.modification or 0
561        local fileformat = "tfm"
562        local filehash   = cleanname(basename(filename))
563        --
564        data = caching and containers.read(filecache,filehash)
565        --
566        if data and data.filetime == filetime and data.filesize == filesize and data.fileformat == fileformat then
567            return data
568        end
569        --
570        local function someerror(m)
571            if not data then
572                data = { }
573            end
574            data.error = m or "fatal error"
575            return data
576        end
577        --
578        local s = openstream(filename)
579        if not s then
580            return someerror()
581        end
582        --
583        local wide       = false
584        local header     = 0
585        local max        = 0
586        local size       = streamsize(s)
587        local glyphs     = table.setmetatableindex(function(t,k)
588            local v = {
589                -- we default because boundary chars have no dimension s
590                width  = 0,
591                height = 0,
592                depth  = 0,
593                italic = 0,
594            }
595            t[k] = v
596            return v
597        end)
598        local parameters = { }
599        local direction  = 0
600        --
601        local lf, lh, bc, ec, nw, nh, nd, ni, nl, nk, ne, np
602        --
603        lf = readcardinal2(s)
604        if lf ~= 0 then
605            header = 6
606            max    = 255
607            wide   = false
608            lh = readcardinal2(s)
609            bc = readcardinal2(s)
610            ec = readcardinal2(s)
611            nw = readcardinal2(s)
612            nh = readcardinal2(s)
613            nd = readcardinal2(s)
614            ni = readcardinal2(s)
615            nl = readcardinal2(s)
616            nk = readcardinal2(s)
617            ne = readcardinal2(s)
618            np = readcardinal2(s)
619        else
620            header = 14
621            max    = 65535
622            wide   = readcardinal4(s) == 0
623            if not wide then
624                return someerror("invalid format")
625            end
626            lf = readcardinal4(s)
627            lh = readcardinal4(s)
628            bc = readcardinal4(s)
629            ec = readcardinal4(s)
630            nw = readcardinal4(s)
631            nh = readcardinal4(s)
632            nd = readcardinal4(s)
633            ni = readcardinal4(s)
634            nl = readcardinal4(s)
635            nk = readcardinal4(s)
636            ne = readcardinal4(s)
637            np = readcardinal4(s)
638            direction = readcardinal4(s)
639        end
640        if (bc > ec + 1) or (ec > max) then
641            return someerror("file is too small")
642        end
643        if bc > max then
644            bc, ec = 1, 0
645        end
646        local nlw  = (wide and 2 or 1) * nl
647        local neew = (wide and 2 or 1) * ne
648        local ncw  = (wide and 2 or 1) * (ec - bc + 1)
649        if lf ~= (header + lh + ncw + nw + nh + nd + ni + nlw + nk + neew + np) then
650            return someerror("file is too small")
651        end
652        if nw == 0 or nh == 0 or nd == 0 or ni == 0 then
653            return someerror("no glyphs")
654        end
655        if lf * 4 > size then
656            return someerror("file is too small")
657        end
658        local slh = lh
659        if lh < 2 then
660            return someerror("file is too small")
661        end
662        local checksum   = readcardinal4(s)
663        local designsize = readcardinal2(s)
664        designsize = designsize * 256 +  readcardinal1(s)
665     -- designsize = designsize *  16 + rshift(readcardinal1(s),4)
666        designsize = designsize *  16 + (readcardinal1(s) >> 4)
667        if designsize < 0xFFFF then
668            return someerror("weird designsize")
669        end
670        --
671        local alpha =  16
672        local z     = designsize
673        while z >= 040000000 do
674         -- z = rshift(z,1)
675            z = (z >> 1) & 0xFFFFFFFF
676            alpha = alpha + alpha
677        end
678        local beta = 256 // alpha
679        alpha = alpha * z
680        --
681        local function readscaled()
682            local a, b, c, d = readbytes(s,4)
683         -- local n = idiv(rshift(rshift(d*z,8)+c*z,8)+b*z,beta)
684            local n = (((((((d * z) >> 8) & 0xFFFFFFFF) + c * z) >> 8) & 0xFFFFFFFF) + b * z) // beta
685            if a == 0 then
686                return n
687            elseif a == 255 then
688                return n - alpha
689            else
690                return 0
691            end
692        end
693        --
694        local function readunscaled()
695            local a, b, c, d = readbytes(s,4)
696            if a > 127 then
697                a = a - 256
698            end
699         -- return a * 0xFFFFF + b * 0xFFF + c * 0xF + rshift(d,4)
700            return a * 0xFFFFF + b * 0xFFF + c * 0xF + ((d >> 4) & 0xFFFFFFFF)
701        end
702        --
703        while lh > 2 do -- can be one-liner
704            skipbytes(s,4)
705            lh = lh - 1
706        end
707        local saved = getposition(s)
708        setposition(s,(header + slh + ncw) * 4 + 1)
709        local widths  = { } for i=0,nw-1 do widths [i] = readscaled() end
710        local heights = { } for i=0,nh-1 do heights[i] = readscaled() end
711        local depths  = { } for i=0,nd-1 do depths [i] = readscaled() end
712        local italics = { } for i=0,ni-1 do italics[i] = readscaled() end
713        if widths[0] ~= 0 or heights[0] ~= 0 or depths[0] ~= 0 then
714            return someerror("invalid dimensions")
715        end
716        --
717        local blabel = nl
718        local bchar  = boundarychar
719        --
720        local ligatures = { }
721        if nl > 0 then
722            for i=0,nl-1 do
723                local a, b, c, d = readbytes(s,4)
724                ligatures[i] = {
725                    skip = a,
726                    nxt  = b,
727                    op   = c,
728                    rem  = d,
729                }
730                if a > 128 then
731                    if 256 * c + d >= nl then
732                        return someerror("invalid ligature table")
733                    end
734                    if a == 255 and i == 0 then
735                        bchar = b
736                    end
737                else
738                    if c < 128 then
739                       -- whatever
740                    elseif 256 * (c - 128) + d >= nk then
741                        return someerror("invalid ligature table")
742                    end
743                    if (a < 128) and (i - 0 + a + 1 >= nl) then
744                        return someerror("invalid ligature table")
745                    end
746                end
747                if a == 255 then
748                    blabel = 256 * c + d
749                end
750            end
751        end
752        local allkerns = { }
753        for i=0,nk-1 do
754            allkerns[i] = readscaled()
755        end
756        local extensibles = { }
757        for i=0,ne-1 do
758            extensibles[i] = wide and {
759                top      = readcardinal2(s),
760                middle   = readcardinal2(s),
761                bottom   = readcardinal2(s),
762                extender = readcardinal2(s),
763            } or {
764                top      = readcardinal1(s),
765                middle   = readcardinal1(s),
766                bottom   = readcardinal1(s),
767                extender = readcardinal1(s),
768            }
769        end
770        for i=1,np do
771            if i == 1 then
772                parameters[i] = readunscaled()
773            else
774                parameters[i] = readscaled()
775            end
776        end
777        for i=1,7 do
778            if not parameters[i] then
779                parameters[i] = 0
780            end
781        end
782        --
783        setposition(s,saved)
784        local extras = false
785        if blabel ~= nl then
786            local k = blabel
787            while true do
788                local l    = ligatures[k]
789                local skip = l.skip
790                if skip <= 128 then
791                 -- if l.op >= 128 then
792                 --     extras = true -- kern
793                 -- else
794                        extras = true -- ligature
795                 -- end
796                end
797                if skip == 0 then
798                    k = k + 1
799                else
800                    if skip >= 128 then
801                       break
802                    end
803                    k = k + skip + 1
804                end
805            end
806        end
807        if extras then
808            local ligas = { }
809            local kerns = { }
810            local k     = blabel
811            while true do
812                local l    = ligatures[k]
813                local skip = l.skip
814                if skip <= 128 then
815                    local nxt = l.nxt
816                    local op  = l.op
817                    local rem = l.rem
818                    if op >= 128 then
819                        kerns[nxt] = allkerns[256 * (op - 128) + rem]
820                    else
821                        ligas[nxt] = { type = op * 2 + 1, char = rem }
822                    end
823                end
824                if skip == 0 then
825                    k = k + 1
826                else
827                    if skip >= 128 then
828                        break;
829                    end
830                    k = k + skip + 1
831                end
832            end
833            if next(kerns) then
834                local glyph     = glyphs[leftboundary]
835                glyph.kerns     = kerns
836                glyph.remainder = 0
837            end
838            if next(ligas) then
839                local glyph     = glyphs[leftboundary]
840                glyph.ligatures = ligas
841                glyph.remainder = 0
842            end
843        end
844        for i=bc,ec do
845            local glyph, width, height, depth, italic, tag, remainder
846            if wide then
847                width     = readcardinal2(s)
848                height    = readcardinal1(s)
849                depth     = readcardinal1(s)
850                italic    = readcardinal1(s)
851                tag       = readcardinal1(s)
852                remainder = readcardinal2(s)
853            else
854                width     = readcardinal1(s)
855                height    = readcardinal1(s)
856             -- depth     = extract(height,0,4)
857                depth     = height        & 0xF
858             -- height    = extract(height,4,4)
859                height    = (height >> 4) & 0xF
860                italic    = readcardinal1(s)
861             -- tag       = extract(italic,0,2)
862                tag       = italic        & 0x03
863             -- italic    = extract(italic,2,6)
864                italic    = (italic >> 2) & 0xFF
865                remainder = readcardinal1(s)
866            end
867            if width == 0 then
868                -- nothing
869            else
870                if width >= nw or height >= nh or depth >= nd or italic >= ni then
871                    return someerror("invalid dimension index")
872                end
873                local extensible, nextinsize
874                if tag == 0 then
875                    -- nothing special
876                else
877                    local r = remainder
878                    if tag == 1 then
879                        if r >= nl then
880                            return someerror("invalid ligature index")
881                        end
882                    elseif tag == 2 then
883                        if r < bc or r > ec then
884                            return someerror("invalid chain index")
885                        end
886                        while r < i do
887                            local g = glyphs[r]
888                            if g.tag ~= list_tag then
889                                break
890                            end
891                            r = g.remainder
892                        end
893                        if r == i then
894                            return someerror("cycles in chain")
895                        end
896                        nextinsize = r
897                    elseif tag == 3 then
898                        if r >= ne then
899                            return someerror("bad extensible")
900                        end
901                        extensible = extensibles[r] -- remainder ?
902                        remainder  = 0
903                    end
904                end
905                local glyph = {
906                    width      = widths [width],
907                    height     = heights[height],
908                    depth      = depths [depth],
909                    italic     = italics[italic],
910                    tag        = tag,
911                 -- index      = i,
912                    remainder  = remainder,
913                    extensible = extensible,
914                    next       = nextinsize,
915                }
916                if extensible then
917                    extensible = toparts(extensible)
918                    if extensible then
919                        glyph.parts            = extensible
920                        glyph.partsorientation = "vertical"
921                        glyph.partsitalic      = glyph.italic
922                    end
923                end
924                glyphs[i] = glyph
925            end
926        end
927        for i=bc,ec do
928            local glyph  = glyphs[i]
929            if glyph.tag == 1 then
930                -- ligature
931                local k = glyph.remainder
932                local l = ligatures[k]
933                if l.skip > 128 then
934                    k = 256 * l.op + l.rem
935                end
936                local ligas = { }
937                local kerns = { }
938                while true do
939                    local l    = ligatures[k]
940                    local skip = l.skip
941                    if skip <= 128 then
942                        local nxt = l.nxt
943                        local op  = l.op
944                        local rem = l.rem
945                        if op >= 128 then
946                            local kern = allkerns[256 * (op - 128) + rem]
947                            if nxt == bchar then
948                                local k =  kerns[rightboundary]
949                                if k then
950                                    logs.report("tfm reader","duplicate boundary for index 0x%X: %p -> %p",i,rightboundary,k,kern)
951                                else
952                                    kerns[rightboundary] = kern
953                                end
954                            end
955                            local k =  kerns[nxt]
956                            if k then
957                                logs.report("tfm reader","duplicate between index 0x%X and 0x%X: %p -> %p",i,nxt,k,kern)
958                            else
959                                kerns[nxt] = kern
960                            end
961                        else
962                            local ligature = { type = op * 2 + 1, char = rem }
963                            if nxt == bchar then
964                                ligas[rightboundary] = ligature
965                            end
966                            ligas[nxt] = ligature -- shared
967                        end
968                    end
969                    if skip == 0 then
970                       k = k + 1
971                    else
972                        if skip >= 128 then
973                            break
974                        end
975                        k = k + skip + 1
976                    end
977                end
978                if next(kerns)then
979                    glyph.kerns     = kerns
980                    glyph.remainder = 0
981                end
982                if next(ligas) then
983                    glyph.ligatures = ligas
984                    glyph.remainder = 0
985                end
986            end
987        end
988        --
989        if bchar ~= boundarychar then
990           glyphs[rightboundary] = copy(glyphs[bchar])
991        end
992        --
993     -- for k, v in next, glyphs do
994     --     v.tag       = nil
995     --     v.remainder = nil
996     -- end
997        --
998        data = {
999            name           = nameonly(filename),
1000            fontarea       = pathpart(filename),
1001            glyphs         = glyphs,
1002            parameters     = parameters,
1003            designsize     = designsize,
1004            size           = designsize,
1005            direction      = direction,
1006         -- checksum       = checksum,
1007         -- embedding      = "unknown",
1008         -- extend         = 1000,
1009         -- slant          = 0,
1010         -- squeeze        = 0,
1011         -- format         = "unknown",
1012         -- identity       = "unknown",
1013         -- mode           = 0,
1014         -- streamprovider = 0,
1015         -- tounicode      = 0,
1016         -- type           = "unknown",
1017         -- units_per_em   = 0,
1018         -- used           = false,
1019         -- width          = 0,
1020         -- writingmode    = "unknown",
1021        }
1022        --
1023        data.filesize   = filesize
1024        data.fileformat = fileformat
1025        data.filetime   = filetime
1026        if caching then
1027            containers.write(filecache,filehash,data)
1028        end
1029        --
1030        return data
1031    end
1032
1033end
1034
1035do
1036
1037    local pushcommand = fonts.helpers.commands.push
1038    local popcommand  = fonts.helpers.commands.pop
1039    local slotcommand = fonts.helpers.commands.slot
1040
1041    local w, x, y, z, f
1042    local stack
1043    local s, result, r
1044    local alpha, beta, z
1045
1046    local function scaled1()
1047        local a = readbytes(s,1)
1048        if a == 0 then
1049            return 0
1050        elseif a == 255 then
1051            return - alpha
1052        else
1053            return 0 -- error
1054        end
1055    end
1056
1057    local function scaled2()
1058        local a, b = readbytes(s,2)
1059        local sw = (b*z) // beta
1060        if a == 0 then
1061            return sw
1062        elseif a == 255 then
1063            return sw - alpha
1064        else
1065            return 0 -- error
1066        end
1067    end
1068
1069    local function scaled3()
1070        local a, b, c = readbytes(s,3)
1071     -- local sw = idiv(rshift(c*z,8)+b*z,beta)
1072        local sw = ((((c * z) >> 8) & 0xFFFFFFFF) + b * z) // beta
1073        if a == 0 then
1074            return sw
1075        elseif a == 255 then
1076            return sw - alpha
1077        else
1078            return 0 -- error
1079        end
1080    end
1081
1082    local function scaled4()
1083        local a, b, c, d = readbytes(s,4)
1084     -- local sw = idiv( rshift(rshift(d*z,8)+(c*z),8)+b*z,beta)
1085        local sw = (((((d * z) >> 8) & 0xFFFFFFFF + (c * z)) >> 8) & 0xFFFFFFFF + b * z) // beta
1086        if a == 0 then
1087            return sw
1088        elseif a == 255 then
1089            return sw - alpha
1090        else
1091            return 0 -- error
1092        end
1093    end
1094
1095    local function dummy()
1096    end
1097
1098    local actions = {
1099
1100        [128] = function() r = r + 1 result[r] = slotcommand[f or 1][readcardinal1(s)] p = p + 1 end,
1101        [129] = function() r = r + 1 result[r] = slotcommand[f or 1][readcardinal2(s)] p = p + 2 end,
1102        [130] = function() r = r + 1 result[r] = slotcommand[f or 1][readcardinal3(s)] p = p + 3 end,
1103        [131] = function() r = r + 1 result[r] = slotcommand[f or 1][readcardinal4(s)] p = p + 4 end,
1104
1105        [132] = function()
1106            r = r + 1
1107            result[r] = { "rule", scaled4(), scaled4() }
1108            p = p + 8
1109        end,
1110
1111        [133] = function()
1112                    r = r + 1 result[r] = pushcommand
1113                    r = r + 1 result[r] = slotcommand[f or 1][readcardinal1(s)]
1114                    r = r + 1 result[r] = popcommand
1115                    p = p + 1
1116                end,
1117        [134] = function()
1118                    r = r + 1 result[r] = pushcommand
1119                    r = r + 1 result[r] = slotcommand[f or 1][readcardinal2(s)]
1120                    r = r + 1 result[r] = popcommand
1121                    p = p + 2
1122                end,
1123        [135] = function()
1124                    r = r + 1 result[r] = pushcommand
1125                    r = r + 1 result[r] = slotcommand[f or 1][readcardinal3(s)]
1126                    r = r + 1 result[r] = popcommand
1127                    p = p + 3
1128                end,
1129        [136] = function()
1130                    r = r + 1 result[r] = pushcommand
1131                    r = r + 1 result[r] = slotcommand[f or 1][readcardinal4(s)]
1132                    r = r + 1 result[r] = popcommand
1133                    p = p + 4
1134                end,
1135
1136        [137] = function()
1137                    r = r + 1 result[r] = pushcommand
1138                    r = r + 1 result[r] = { "rule", scaled4(), scaled4() }
1139                    r = r + 1 result[r] = popcommand
1140                    p = p + 8
1141                end,
1142
1143        [138] = dummy, -- nop
1144        [139] = dummy, -- bop
1145        [140] = dummy, -- eop
1146
1147        [141] = function()
1148                    insert(stack, { w, x, y, z })
1149                    r = r + 1
1150                    result[r] = pushcommand
1151                end,
1152        [142] = function()
1153                    local t = remove(stack)
1154                    if t then
1155                        w, x, y, z = t[1], t[2], t[3], t[4]
1156                        r = r + 1
1157                        result[r] = popcommand
1158                    end
1159                end,
1160
1161        [143] = function() r = r + 1 result[r] = { "right", scaled1() } p = p + 1 end,
1162        [144] = function() r = r + 1 result[r] = { "right", scaled2() } p = p + 2 end,
1163        [145] = function() r = r + 1 result[r] = { "right", scaled3() } p = p + 3 end,
1164        [146] = function() r = r + 1 result[r] = { "right", scaled4() } p = p + 4 end,
1165
1166        [148] = function() w = scaled1() r = r + 1 result[r] = { "right", w } p = p + 1 end,
1167        [149] = function() w = scaled2() r = r + 1 result[r] = { "right", w } p = p + 2 end,
1168        [150] = function() w = scaled3() r = r + 1 result[r] = { "right", w } p = p + 3 end,
1169        [151] = function() w = scaled4() r = r + 1 result[r] = { "right", w } p = p + 4 end,
1170
1171        [153] = function() x = scaled1() r = r + 1 result[r] = { "right", x } p = p + 1 end,
1172        [154] = function() x = scaled2() r = r + 1 result[r] = { "right", x } p = p + 2 end,
1173        [155] = function() x = scaled3() r = r + 1 result[r] = { "right", x } p = p + 3 end,
1174        [156] = function() x = scaled4() r = r + 1 result[r] = { "right", x } p = p + 4 end,
1175
1176        [157] = function() r = r + 1 result[r] = { "down", scaled1() } p = p + 1 end,
1177        [158] = function() r = r + 1 result[r] = { "down", scaled2() } p = p + 2 end,
1178        [159] = function() r = r + 1 result[r] = { "down", scaled3() } p = p + 3 end,
1179        [160] = function() r = r + 1 result[r] = { "down", scaled4() } p = p + 4 end,
1180
1181        [162] = function() y = scaled1() r = r + 1 result[r] = { "down", y } p = p + 1 end,
1182        [163] = function() y = scaled2() r = r + 1 result[r] = { "down", y } p = p + 2 end,
1183        [164] = function() y = scaled3() r = r + 1 result[r] = { "down", y } p = p + 3 end,
1184        [165] = function() y = scaled3() r = r + 1 result[r] = { "down", y } p = p + 4 end,
1185
1186        [167] = function() z = scaled1() r = r + 1 ; result[r] = { "down", z } p = p + 4 end,
1187        [168] = function() z = scaled2() r = r + 1 ; result[r] = { "down", z } p = p + 4 end,
1188        [169] = function() z = scaled3() r = r + 1 ; result[r] = { "down", z } p = p + 4 end,
1189        [170] = function() z = scaled4() r = r + 1 ; result[r] = { "down", z } p = p + 4 end,
1190
1191        [147] = function() r = r + 1 result[r] = { "right", w } end,
1192        [152] = function() r = r + 1 result[r] = { "right", x } end,
1193        [161] = function() r = r + 1 result[r] = { "down",  y } end,
1194        [166] = function() r = r + 1 result[r] = { "down",  z } end,
1195
1196        [235] = function() f = readcardinal1(s) p = p + 1 end,
1197        [236] = function() f = readcardinal2(s) p = p + 3 end,
1198        [237] = function() f = readcardinal3(s) p = p + 3 end,
1199        [238] = function() f = readcardinal4(s) p = p + 4 end,
1200
1201        [239] = function() local n = readcardinal1(s) r = r + 1 result[r] = { "special", readstring(s,n) } p = p + 1 + n end,
1202        [240] = function() local n = readcardinal2(s) r = r + 1 result[r] = { "special", readstring(s,n) } p = p + 2 + n end,
1203        [241] = function() local n = readcardinal3(s) r = r + 1 result[r] = { "special", readstring(s,n) } p = p + 3 + n end,
1204        [242] = function() local n = readcardinal4(s) r = r + 1 result[r] = { "special", readstring(s,n) } p = p + 4 + n end,
1205
1206        [250] = function() local n = readcardinal1(s) r = r + 1 result[r] = { "pdf", readstring(s,n) } p = p + 1 + n end,
1207        [251] = function() local n = readcardinal2(s) r = r + 1 result[r] = { "pdf", readstring(s,n) } p = p + 2 + n end,
1208        [252] = function() local n = readcardinal3(s) r = r + 1 result[r] = { "pdf", readstring(s,n) } p = p + 3 + n end,
1209        [253] = function() local n = readcardinal4(s) r = r + 1 result[r] = { "pdf", readstring(s,n) } p = p + 4 + n end,
1210
1211    }
1212
1213    table.setmetatableindex(actions,function(t,cmd)
1214        local v
1215        if cmd >= 0 and cmd <= 127 then
1216            v = function()
1217                if f == 0 then
1218                    f = 1
1219                end
1220                r = r + 1 ; result[r] = slotcommand[f][cmd]
1221            end
1222        elseif cmd >= 171 and cmd <= 234 then
1223            cmd = cmd - 170
1224            v = function()
1225                r = r + 1 ; result[r] = { "font", cmd }
1226            end
1227        else
1228            v = dummy
1229        end
1230        t[cmd] = v
1231        return v
1232    end)
1233
1234    function readers.loadvf(filename,data)
1235        --
1236        local function someerror(m)
1237            if not data then
1238                data = { }
1239            end
1240            data.error = m or "fatal error"
1241            return data
1242        end
1243        --
1244        s = openstream(filename)
1245        if not s then
1246            return someerror()
1247        end
1248        --
1249        local cmd = readcardinal1(s)
1250        if cmd ~= 247 then
1251            return someerror("bad preamble")
1252        end
1253        cmd = readcardinal1(s)
1254        if cmd ~= 202 then
1255            return someerror("bad version")
1256        end
1257        local header     = readstring(s,readcardinal1(s))
1258        local checksum   = readcardinal4(s)
1259        local designsize = readcardinal4(s) // 16
1260        local fonts      = data and data.fonts  or { }
1261        local glyphs     = data and data.glyphs or { }
1262        --
1263        alpha =  16
1264        z     = designsize
1265        while z >= 040000000 do
1266         -- z = rshift(z,1)
1267            z = (z >> 1) & 0xFFFFFFFF
1268            alpha = alpha + alpha
1269        end
1270        beta  = 256 // alpha
1271        alpha = alpha * z
1272        --
1273        cmd = readcardinal1(s)
1274        while true do
1275            local n
1276            if cmd == 243 then
1277                n = readcardinal1(s) + 1
1278            elseif cmd == 244 then
1279                n = readcardinal2(s) + 1
1280            elseif cmd == 245 then
1281                n = readcardinal3(s) + 1
1282            elseif cmd == 246 then
1283                n = readcardinal4(s) + 1
1284            else
1285                break
1286            end
1287            local checksum   = skipbytes(s,4)
1288            local size       = scaled4()
1289            local designsize = readcardinal4(s) // 16
1290            local pathlen    = readcardinal1(s)
1291            local namelen    = readcardinal1(s)
1292            local path       = readstring(s,pathlen)
1293            local name       = readstring(s,namelen)
1294            fonts[n] = { path = path, name = name, size = size }
1295            cmd = readcardinal1(s)
1296        end
1297        local index = 0
1298        while cmd and cmd <= 242 do
1299            local width    = 0
1300            local length   = 0
1301            local checksum = 0
1302            if cmd == 242 then
1303                length   = readcardinal4(s)
1304                checksum = readcardinal4(s)
1305                width    = readcardinal4(s)
1306            else
1307                length   = cmd
1308                checksum = readcardinal1(s)
1309                width    = readcardinal3(s)
1310            end
1311            w, x, y, z, f = 0, 0, 0, 0, false
1312            stack, result, r, p = { }, { }, 0, 0
1313            while p < length do
1314                local cmd = readcardinal1(s)
1315                p = p + 1
1316                actions[cmd]()
1317            end
1318            local glyph = glyphs[index]
1319            if glyph then
1320                glyph.width    = width
1321                glyph.commands = result
1322            else
1323                glyphs[index] = {
1324                    width    = width,
1325                    commands = result,
1326                }
1327            end
1328            index = index + 1
1329            if #stack > 0 then
1330                -- error: more pushes than pops
1331            end
1332            if packet_length ~= 0 then
1333                -- error: invalid packet length
1334            end
1335            cmd = readcardinal1(s)
1336        end
1337        if readcardinal1(s) ~= 248 then
1338            -- error: no post
1339        end
1340        s, result, r = nil, nil, nil
1341        if data then
1342            data.glyphs = data.glyphs or glyphs
1343            data.fonts  = data.fonts  or fonts
1344            return data
1345        else
1346            return {
1347                name       = nameonly(filename),
1348                fontarea   = pathpart(filename),
1349                glyphs     = glyphs,
1350                designsize = designsize,
1351                header     = header,
1352                fonts      = fonts,
1353            }
1354        end
1355    end
1356
1357    -- the replacement loader (not sparse):
1358
1359    function readers.loadtfmvf(tfmname,size)
1360        local vfname  = addsuffix(nameonly(tfmfile),"vf")
1361        local tfmfile = tfmname
1362        local vffile  = findbinfile(vfname,"ovf")
1363        if tfmfile and tfmfile ~= "" then
1364            if size < 0 then
1365                size = (65536 * -size) // 100
1366            end
1367            local data = readers.loadtfm(tfmfile)
1368            if data.error then
1369                return data
1370            end
1371            if vffile and vffile ~= "" then
1372                data = readers.loadvf(vffile,data)
1373                if data.error then
1374                    return data
1375                end
1376            end
1377            local designsize = data.designsize
1378            local glyphs     = data.glyphs
1379            local parameters = data.parameters
1380            local fonts      = data.fonts
1381            if size ~= designsize then
1382                local factor = size / designsize
1383                for index, glyph in next, glyphs do
1384                    if next(glyph) then
1385                        glyph.width  = round(factor*glyph.width)
1386                        glyph.height = round(factor*glyph.height)
1387                        glyph.depth  = round(factor*glyph.depth)
1388                        local italic = glyph.italic
1389                        if italic == 0 then
1390                            glyph.italic = nil
1391                        else
1392                            glyph.italic = round(factor*glyph.italic)
1393                        end
1394                        --
1395                        local kerns = glyph.kerns
1396                        if kerns then
1397                            for index, kern in next, kerns do
1398                                kerns[index] = round(factor*kern)
1399                            end
1400                        end
1401                        --
1402                        local commands = glyph.commands
1403                        if commands then
1404                            for i=1,#commands do
1405                                local c = commands[i]
1406                                local t = c[1]
1407                                if t == "down" or t == "right" then
1408                                    c[2] = round(factor*c[2])
1409                                elseif t == "rule" then
1410                                    c[2] = round(factor*c[2])
1411                                    c[3] = round(factor*c[3])
1412                                end
1413                            end
1414                        end
1415                    else
1416                        glyphs[index] = nil
1417                    end
1418                end
1419                for i=2,30 do
1420                    local p = parameters[i]
1421                    if p then
1422                        parameters[i] = round(factor*p)
1423                    else
1424                        break
1425                    end
1426                end
1427                if fonts then
1428                    for k, v in next, fonts do
1429                        v.size = round(factor*v.size)
1430                    end
1431                end
1432            else
1433                for index, glyph in next, glyphs do
1434                    if next(glyph) then
1435                        if glyph.italic == 0 then
1436                            glyph.italic = nil
1437                        end
1438                    else
1439                        glyphs[index] = nil
1440                    end
1441                end
1442            end
1443            --
1444            parameters.slant        = parameters[1]
1445            parameters.space        = parameters[2]
1446            parameters.spacestretch = parameters[3]
1447            parameters.spaceshrink  = parameters[4]
1448            parameters.xheight      = parameters[5]
1449            parameters.quad         = parameters[6]
1450            parameters.extraspace   = parameters[7]
1451            --
1452            for i=1,7 do
1453                parameters[i] = nil -- so no danger for async
1454            end
1455            --
1456            data.characters = glyphs
1457            data.glyphs     = nil
1458            data.size       = size
1459            -- we assume type1 for now ... maybe the format should be unknown
1460            data.filename   = tfmfile -- file.replacesuffix(tfmfile,"pfb")
1461            data.format     = "unknown"
1462            --
1463            return data
1464        end
1465    end
1466
1467end
1468
1469function resolvers.findpk(font,resolution)
1470    local filename = addsuffix(font,(resolution or "") .. "pk")
1471    local fullname = findbinfile(filename) or ""
1472    if fullname == "" then
1473        filename = addsuffix(font,"pk")
1474        fullname = findbinfile(filename) or ""
1475    end
1476    return fullname
1477end
1478
1479-- inspect(readers.loadtfmvf(resolvers.findfile("mi-iwonari.tfm")))
1480-- inspect(readers.loadtfm(resolvers.findfile("texnansi-palatinonova-regular.tfm")))
1481-- inspect(readers.loadtfm(resolvers.findfile("cmex10.tfm")))
1482-- inspect(readers.loadtfm(resolvers.findfile("cmr10.tfm")))
1483-- local t = readers.loadtfmvf("texnansi-lte50019.tfm")
1484-- inspect(t)
1485