math-ini.lmt /size: 43 Kb    last modification: 2025-02-21 11:03
1if not modules then modules = { } end modules ['math-ini'] = {
2    version   = 1.001,
3    comment   = "companion to math-ini.mkiv",
4    author    = "Hans Hagen, PRAGMA-ADE, Hasselt NL",
5    copyright = "PRAGMA ADE / ConTeXt Development Team",
6    license   = "see context related readme files"
7}
8
9-- The way we do math in \CONTEXT\ \MKIV\ differs from other macro packages so you
10-- should not mix the somewhat unique (and bit weird) approach here with the more
11-- traditional (\TEX) approach. Also, we use char-def.lua as starting point and that
12-- file is quite \CONTEXT\ specific. When we added math to that there was no
13-- interest (quite the contrary) so we didn't went generic there which in retrospect
14-- also gives us the freedom to add more information, something that happens
15-- occasionally. Because that file is shared between \MKIV\ and \LMTX\ some
16-- information is only used by \LMTX. We also have quite some runs over the math
17-- list but that has been so since we started and performance will not degrade much
18-- by it; after all math is not that demanding. More details can be found in the
19-- manuals that discuss math. Most code (and concepts) date from 2005 so maybe I
20-- will upgrade the lot some day, although it has been adapted on the way to the
21-- changes in the engine(s).
22
23local next, type = next, type
24local formatters, find, nospaces = string.formatters, string.find, string.nospaces
25local utfchar, utfbyte = utf.char, utf.byte
26local sortedhash = table.sortedhash
27local toboolean = toboolean
28
29local context               = context
30local implement             = interfaces.implement
31
32local ctx_doifelsesomething = commands.doifelsesomething
33
34local trace_defining        = false  trackers.register("math.defining", function(v) trace_defining = v end)
35
36local report_math           = logs.reporter("mathematics","initializing")
37
38mathematics                 = mathematics or { }
39local mathematics           = mathematics
40
41mathematics.extrabase       = fonts.privateoffsets.mathextrabase -- here we push some virtuals
42mathematics.privatebase     = fonts.privateoffsets.mathbase      -- here we push the ex
43
44local unsetvalue            <const> = attributes.unsetvalue
45
46local allocate              = utilities.storage.allocate
47local chardata              = characters.data
48
49local texsetattribute       = tex.setattribute
50local setmathcode           = tex.setmathcode
51----- setdelcode            = tex.setdelcode -- we no longer set these as the engine also accepts otherwise
52local texintegerdef         = tex.integerdef
53
54local getfontoffamily       = tex.getfontoffamily
55
56local fontdata              = fonts.hashes.identifiers
57local fontchardata          = fonts.hashes.characters
58
59-- These are different from mkiv with luatex.
60
61local classes          = allocate { unset = 64 } -- or -1
62local classnames       = allocate { }
63local maxengineclass   = 63
64local lastengineclass  = 0
65local lastprivateclass = maxengineclass
66
67for k, v in next, nodes.noadcodes do
68    if type(k) == "string" then
69        classes[k] = v
70--         local n = classnames[v]
71--         if not n or #k < #n then
72--             classnames[v] = k
73--         end
74    elseif k > lastengineclass then
75        lastengineclass = k
76    end
77end
78
79local ordinary_class    = classes.ordinary
80local operator_class    = classes.operator
81local binary_class      = classes.binary
82local relation_class    = classes.relation
83local open_class        = classes.open
84local close_class       = classes.close
85local variable_class    = classes.variable
86local punctuation_class = classes.punctuation
87local middle_class      = classes.middle
88local accent_class      = classes.accent
89local radical_class     = classes.radical
90local fraction_class    = classes.fraction
91local under_class       = classes.under
92local over_class        = classes.over
93local fenced_class      = classes.fenced
94local ghost_class       = classes.ghost
95
96-- these will go
97
98classes.ord             = ordinary_class
99classes.op              = operator_class
100classes.bin             = binary_class
101classes.rel             = relation_class
102classes.opening         = open_class         -- will go
103classes.closing         = close_class        -- will go
104classes.punct           = punctuation_class
105classes.frac            = fraction_class
106classes.rad             = radical_class
107classes.fen             = fenced_class
108classes.gst             = ghost_class
109
110-- these will go too
111
112classes.limop           = operator_class
113classes.limoperator     = operator_class
114classes.nolop           = operator_class
115classes.nolimoperator   = operator_class
116classes.large           = operator_class
117classes.largeoperator   = operator_class
118
119-- special in the engine : variable active inner vcenter
120
121local glyphcodes = nodes.glyphcodes
122
123local function registerengineclass(name,short)
124    local class = classes[name]
125    if not class then
126        if lastengineclass < maxengineclass then
127            lastengineclass = lastengineclass + 1
128            class = lastengineclass
129            classnames[class] = short or name
130        else
131            class = ordinary_class
132        end
133    else
134        classnames[class] = short or name
135    end
136    classes[class] = name
137    classes[name] = class
138    local subtype = class + 31 -- todo magic constant
139    glyphcodes[subtype] = name
140    glyphcodes[name] = subtype
141    return class
142end
143
144-- predefined classes
145
146registerengineclass("ordinary",    "ord")
147registerengineclass("operator",    "ope")
148registerengineclass("binary",      "bin")
149registerengineclass("relation",    "rel")
150registerengineclass("open",        "ope")
151registerengineclass("close",       "clo")
152registerengineclass("punctuation", "pun")
153registerengineclass("variable",    "var") -- not used
154registerengineclass("active",      "act") -- not used
155registerengineclass("inner",       "inn") -- not used
156registerengineclass("middle",      "mid")
157registerengineclass("accent",      "acc")
158registerengineclass("radical",     "rad")
159registerengineclass("fraction",    "fra")
160registerengineclass("under",       "und")
161registerengineclass("over",        "ove")
162registerengineclass("fenced",      "fen")
163registerengineclass("ghost",       "gho")
164registerengineclass("vcenter",     "vce") -- not used
165
166-- additional classes
167
168registerengineclass("explicit",        "xpl")
169registerengineclass("imaginary",       "img")
170registerengineclass("differential",    "dif")
171registerengineclass("exponential",     "exp")
172registerengineclass("integral",        "int")
173registerengineclass("ellipsis",        "ell")
174registerengineclass("function",        "fnc")
175registerengineclass("digit",           "dig")  local division_class =
176registerengineclass("division",        "div")
177registerengineclass("factorial",       "fac")
178registerengineclass("wrapped",         "wra")
179registerengineclass("construct",       "con")
180registerengineclass("dimension",       "dim")
181registerengineclass("unary",           "una")
182registerengineclass("textpunctuation", "tpu")
183registerengineclass("unspaced",        "uns")
184registerengineclass("experimental",    "exp")
185registerengineclass("fake",            "fak")
186registerengineclass("numbergroup",     "ngr")
187
188registerengineclass("maybeordinary",   "mor")
189registerengineclass("mayberelation",   "mre")
190registerengineclass("maybebinary",     "mbi")
191
192registerengineclass("chemicalbond",    "chb")
193registerengineclass("implication",     "imp")
194
195registerengineclass("continuation",    "ctn")
196
197local specialclasses = tex.specialmathclasscodes
198
199classes["all"]   = specialclasses["all"]    classnames[specialclasses["all"]  ] = "all"
200classes["begin"] = specialclasses["begin"]  classnames[specialclasses["begin"]] = "beg"
201classes["end"]   = specialclasses["end"]    classnames[specialclasses["end"]  ] = "end"
202
203callbacks.register("get_noad_class", function(n) return classnames[n] end,"provide math class name")
204
205-- inspect(classes) os.exit()
206
207local function registerprivateclass(name,parent)
208    local class = parent and classes[parent] or classes[name]
209    if not class then
210        lastprivateclass = lastprivateclass + 1
211        class = lastprivateclass
212        classes[name] = class
213        -- also setup
214    end
215    return class
216end
217
218local function toengineclass(class)
219    if type(class) == "string" then
220        return classes[class] or ordinary_class
221    elseif class > lastengineclass then
222        return ordinary_class
223    else
224        return class
225    end
226end
227
228implement {
229    name      = "registerengineclass",
230    public    = true,
231    protected = true,
232    arguments = { "optional", "optional" },
233    actions   = registerengineclass,
234}
235
236local topaccent_class    = registerprivateclass("topaccent")
237local bottomaccent_class = registerprivateclass("bottomaccent")
238local delimiter_class    = registerprivateclass("delimiter")
239local root_class         = registerprivateclass("root")
240----- prime_class        = registerprivateclass("prime")
241
242registerprivateclass("botaccent","bottomaccent")
243
244local accents = allocate {
245    accent       = true, -- some can be both
246    topaccent    = true,  [topaccent_class]    = true,
247    bottomaccent = true,  [bottomaccent_class] = true,
248    botaccent    = true,
249    under        = true,  [under_class]        = true,
250    over         = true,  [over_class]         = true,
251    unknown      = false,
252}
253
254local integer_value <const> = tokens.values.integer
255
256implement {
257    name      = "mathclassvalue",
258 -- usage     = "value",
259    public    = true,
260    arguments = "string",
261    actions = function(name)
262     -- return integer_value, classes[name] or ordinary_class
263        context(tostring(classes[name] or ordinary_class))
264    end
265}
266
267-- used in math-tag: so there we need to make things ord etc to fit within
268-- mathml
269
270local codes = allocate {
271    variable       = variable_class,    [variable_class]    = "variable",
272    ordinary       = ordinary_class,    [ordinary_class]    = "ordinary",
273    largeoperator  = operator_class,    [operator_class]    = "largeoperator",
274    binaryoperator = binary_class,      [binary_class]      = "binaryoperator",
275    relation       = relation_class,    [relation_class]    = "relation",
276    openingsymbol  = open_class,        [open_class]        = "openingsymbol",
277    closingsymbol  = close_class,       [close_class]       = "closingsymbol",
278    punctuation    = punctuation_class, [punctuation_class] = "punctuation",
279    middlesymbol   = middle_class,      [middle_class]      = "middlesymbol",
280}
281
282local extensibles = allocate {
283           unknown    = 0,
284    l = 1, left       = 1,
285    r = 2, right      = 2,
286    h = 3, horizontal = 3,-- lr or rl
287    u = 5, up         = 4,
288    d = 5, down       = 5,
289    v = 6, vertical   = 6,-- ud or du
290    m = 7, mixed      = 7,
291}
292
293table.setmetatableindex(extensibles,function(t,k) t[k] = 0 return 0 end)
294
295local virtualized = allocate {
296}
297
298function mathematics.virtualize(unicode,virtual)
299
300    local function virtualize(k,v)
301        local c = virtualized[k]
302        if c == v then
303            report_math("character %C is already virtualized to %C",k,v)
304        elseif c then
305            report_math("character %C is already virtualized to %C, ignoring mapping to %C",k,c,v)
306        else
307            virtualized[k] = v
308        end
309    end
310
311    if type(unicode) == "table" then
312        for k, v in next, unicode do
313            virtualize(k,v)
314        end
315    elseif type(unicode) == "number" and type(virtual) == "number" then
316        virtualize(unicode,virtual)
317 -- else
318        -- error
319    end
320end
321
322mathematics.extensibles   = extensibles
323mathematics.classes       = classes
324mathematics.toengineclass = toengineclass
325mathematics.classnames    = classnames
326mathematics.codes         = codes
327-----------.accents       = codes
328mathematics.virtualized   = virtualized
329
330-- This is relatively new and experimental:
331
332do
333
334    local dictionaries       = mathematics.dictionaries or { }
335    mathematics.dictionaries = dictionaries
336
337    local names    = dictionaries.names    or utilities.storage.allocate()
338    local groups   = dictionaries.groups   or utilities.storage.allocate()
339    local data     = dictionaries.data     or utilities.storage.allocate()
340    local sets     = dictionaries.sets     or utilities.storage.allocate()
341    local variants = dictionaries.variants or utilities.storage.allocate() -- todo: get from char-def
342    local defaults = dictionaries.defaults or utilities.storage.allocate() -- todo: get from char-def
343
344    storage.register("mathematics/dictionaries/names",    names,    "mathematics.dictionaries.names")
345    storage.register("mathematics/dictionaries/groups",   groups,   "mathematics.dictionaries.groups")
346    storage.register("mathematics/dictionaries/data",     data,     "mathematics.dictionaries.data")
347    storage.register("mathematics/dictionaries/sets",     sets,     "mathematics.dictionaries.sets")
348    storage.register("mathematics/dictionaries/variants", variants, "mathematics.dictionaries.variants")
349    storage.register("mathematics/dictionaries/defaults", defaults, "mathematics.dictionaries.defaults")
350
351    dictionaries.names    = dictionaries.names    or names
352    dictionaries.groups   = dictionaries.groups   or groups
353    dictionaries.data     = dictionaries.data     or data
354    dictionaries.sets     = dictionaries.sets     or sets
355    dictionaries.variants = dictionaries.variants or variants
356    dictionaries.defaults = dictionaries.defaults or defaults
357
358    local i_everygroup <const> = 0xFFFF
359    local s_everygroup <const> = "everygroup"
360
361    names [s_everygroup] = i_everygroup
362    names [i_everygroup] = i_everygroup
363    groups[i_everygroup] = s_everygroup
364    data  [i_everygroup] = { }
365
366    if not sets.n then
367        sets.n = 0
368    end
369
370    function dictionaries.registergroup(name)
371        local group = rawget(names,name)
372        if not group then
373            group = #groups + 1
374            names[name]   = group
375            names[group]  = group -- hm
376            groups[group] = name
377            data[group]   = { }
378            local csname  = "math" .. nospaces(name) .. "dictionary"
379            texintegerdef(csname,group,"immutable")
380        end
381        return group
382    end
383
384    function dictionaries.registergroupset(name,set)
385        local s = sets[name]
386        if not s then
387            if set == "every" then
388                s = {
389                    group = i_everygroup,
390                }
391                sets[name] = s
392            else
393                local d = dictionaries.registergroup(name)
394                local n = sets.n + 1
395                local l = utilities.parsers.settings_to_array(set)
396                local g = { }
397                for i=1,#l do
398                    local n = names[l[i]]
399                    if n then
400                        g[#g+1] = n -- ordered
401                    end
402                end
403                s = {
404                    names  = l,
405                    groups = g,
406                    group  = d,
407                }
408                sets[name] = s
409                sets[d]    = s
410            end
411        end
412    end
413
414    -- TODO: check 'minus' as it reports true
415
416    function dictionaries.groupset(name)
417        return sets[name] or { }
418    end
419
420    function dictionaries.groupsetgroup(name)
421        if name == "every" or name == s_everygroup then
422            return i_everygroup
423        else
424            local s = sets[name]
425            if s then
426                return s.group
427            else
428                return names[name] or 0
429            end
430        end
431    end
432
433    function dictionaries.registercharacter(group,index,description,class,name) -- name is diagnostic
434        local d = names[group] -- can be number or string
435        if d then
436            data[d][index] = description or true
437            local v = variants[index]
438            if type(class) == "string" then
439                class = classes[class]
440            end
441            if not class then
442                class = true
443            end
444            if v then
445                v[d] = class
446            else
447                variants[index] = { [d] = class }
448            end
449            if not defaults[index] then
450                defaults[index] = d
451            end
452        end
453--         print(group,index,description,class,name)
454    end
455
456    function dictionaries.name(group,index) -- number, number
457        group = names[group] or i_everygroup
458        if group == i_everygroup then
459            for i=1,#groups do
460                local d = data[i]
461                local n = d[index]
462                if type(n) == "string" then
463                    return n
464                end
465            end
466        elseif group then
467            local d = data[group]
468            if d then
469                local n = d[index]
470                if type(n) == "string" then
471                    return n
472                end
473            end
474            local s = sets[group]
475            if s then
476                local g = s.groups
477                for i=1,#g do
478                    d = data[g[i]]
479                    local n = d[index]
480                    if type(n) == "string" then
481                        return n
482                    end
483                end
484            end
485        end
486        return false
487    end
488
489    implement {
490        name      = "registergroupset",
491        arguments = "2 strings",
492        actions   = dictionaries.registergroupset,
493    }
494
495    implement {
496        name      = "groupsetgroup",
497        arguments = "string",
498        actions   = { dictionaries.groupsetgroup, context },
499    }
500
501    local f_dictionary = false
502    local whatdetail   = "all"
503
504    local function trace(n,properties,group,index,font,char)
505     -- local properties, group, index, font, char = nodes.nuts.getchardict(nodes.nuts.tonut(n))
506        if whatdetail and (properties ~= 0 or group ~= 0 or index ~= 0) then
507            local char = fontchardata[font][char]
508            if char or whatdetail == "all" then
509                local unicode = char and char.unicode
510                if unicode then
511                    local groupname = groups[group]
512                    local indexname = false
513                    if groupname then
514                        indexname = data[group][index] -- dictionaries.data
515                    else
516                        groupname = "unknown"
517                    end
518                    if not indexname or indexname == true then
519                        indexname = chardata[unicode]
520                        indexname = indexname and indexname.description or "unknown"
521                    end
522                    if not f_dictionary then
523                        f_dictionary = formatters["properties [%04X:%04X:%04X] [%s] %U : %s"]
524                    end
525                    return f_dictionary(properties,group,index,groupname,unicode,indexname)
526                end
527            end
528        end
529    end
530
531    trackers.register("math.dictionaries",function(v) whatdetail = v end)
532
533    callbacks.register("get_math_dictionary",trace,"provide math dictionary details")
534
535    -- This is experimental and a prelude to the long pending "relate math rendering to
536    -- some field" wish. In TeX characters and symbols are grouped by class but that is
537    -- mostly related to spacing etc. while we actually want to group by meaning. A
538    -- reasonable but incomplete starting point is:
539    --
540    -- https://www.w3.org/TR/MathML3/appendixa.html#parsing_DefEncAtt
541    --
542    -- But it has some weird short names mixed with long ones (and a strange suddenly
543    -- uppercase: Differential-Operator) but we are not bound to that at all. We will
544    -- probably remove and add categories anyway. This openmath stuff looks a bit
545    -- abandoned but we can use it as a start and playground anyway.
546    --
547    -- The char-def.lua file will have mathgroup entries reflecting this.
548    --
549    -- This is a good one (with nice roll-overs too):
550    --
551    -- https://en.wikipedia.org/wiki/List_of_mathematical_symbols_by_subject
552
553    if environment.initex then
554
555        local registergroup = mathematics.dictionaries.registergroup
556
557        registergroup("default")
558
559        registergroup("binary relation")
560        registergroup("binary set relation")
561        registergroup("integral")
562        registergroup("limit")
563        registergroup("number set")
564        registergroup("postfix operator")
565        registergroup("prime")
566        registergroup("binary operator")
567        registergroup("binary vector")
568        registergroup("binary arithmetic")     -- operator
569        registergroup("binary logical")
570        registergroup("binary set")
571        registergroup("constant arithmetic")
572        registergroup("constant set")
573        registergroup("differential")
574        registergroup("differential2")
575        registergroup("factorial")
576        registergroup("interval")
577        registergroup("quantifier")
578        registergroup("unary set")             -- check forall exists etc
579        registergroup("constant logical")      -- new one
580        registergroup("partial")               -- partial differential
581        registergroup("nary operator")         -- new one
582        registergroup("nary logical")
583        registergroup("specifier")
584        registergroup("specifier2")
585        registergroup("pause")
586        registergroup("punctuation")
587     -- registergroup("grouped")
588        registergroup("unary logical")
589        registergroup("whatever")
590        registergroup("whatever2")
591
592     -- registergroup("binary linear algebra")
593     -- registergroup("lambda")
594     -- registergroup("nary arithmetic")       -- see operator
595     -- registergroup("nary constructor")
596     -- registergroup("nary functional")
597     -- registergroup("nary linear algebra")
598     -- registergroup("nary minmax")
599     -- registergroup("nary relation")
600     -- registergroup("nary set list")
601     -- registergroup("nary set relation")
602     -- registergroup("nary set")
603     -- registergroup("nary statistics")
604     -- registergroup("product")
605     -- registergroup("unary arithmetic")      -- operator
606     -- registergroup("unary elementary")      -- sin cos ln sqrt
607     -- registergroup("unary functional")
608     -- registergroup("unary linear algebra")
609     -- registergroup("unary logical")
610     -- registergroup("unary vector")
611
612    end
613
614    -- \Umathdictdef\vdash 1 \mathbinarylogicaldictionary "22A2 \mathrelationcode 0 "22A2
615    --
616    -- \startluacode
617    --     mathematics.dictionaries.registercharacter("binary logical",0x22A2,"implies")
618    -- \stopluacode
619
620end
621
622do
623
624    local skip = {
625       [accent_class]       = true,
626       [topaccent_class]    = true,
627       [bottomaccent_class] = true,
628       [over_class]         = true,
629       [under_class]        = true,
630       [radical_class]      = true,
631       [root_class]         = true,
632    }
633
634    local registercharacter = mathematics.dictionaries.registercharacter
635    local groupnames        = mathematics.dictionaries.names
636
637    local i_everygroup <const> = 0xFFFF
638
639    local setmathcharacter = function(class,family,slot,unicode,mset,group,meaning)
640        if mset and class ~= ordinary_class then
641            setmathcode("global",slot,class,family,unicode)
642            mset = false
643        end
644        if group then
645            group = groupnames[group] or 0
646            if group ~= 0 then
647                -- which one
648                registercharacter(group,unicode,meaning,class)
649             -- registercharacter(group,slot,meaning,class)
650            end
651        end
652        return mset
653    end
654
655    local function report(class,family,unicode,name,group)
656        local nametype = type(name)
657        if not group then
658            group = "no group"
659        end
660        if nametype == "string" then
661            report_math("class %a, family %a, char %C, name %a, group %a",class,family,unicode,name,group)
662        elseif nametype == "number" then
663            report_math("class %a, family %a, char %C, number %U, group %a",class,family,unicode,name,group)
664        else
665            report_math("class %a, family %a, char %C, group %a",class,family,unicode,group)
666        end
667    end
668
669    local texmathchardef = tex.mathchardef
670
671    local setmathsymbol = function(name,class,family,slot,stretch,group,meaning) -- hex is nicer for tracing
672        if skip[class] then
673            return -- only in mkiv
674     -- elseif class == open_class or class == close_class or class == middle_class then
675        else
676            if class == delimiter_class then -- open close or middle (bars)
677                class = ordinary_class
678            end
679            if group then
680                group = groupnames[group] or 0
681                if group ~= 0 then
682                    texmathchardef(name,class,family,slot,"permanent",0x1,group,slot)
683                    registercharacter(group,slot,meaning,class,name)
684                    return
685                end
686            end
687            texmathchardef(name,class,family,slot,"permanent")
688        end
689    end
690
691    mathematics.setmathsymbol = setmathsymbol
692
693    function mathematics.define()
694        if trace_defining then
695            logs.startfilelogging(report_math,"math defined from character definitions")
696        end
697        local family = 0
698        local data   = characters.data
699        --
700        local function remap(first,last)
701            for unicode=utfbyte(first),utfbyte(last) do
702                setmathcode("global",unicode,ordinary_class,family,unicode)
703            end
704        end
705        remap("0","9")
706        remap("A","Z")
707        remap("a","z")
708        --
709     -- setdelcode("global",0x2E,0,0,0,0) -- period is special -- still?
710        --
711        for unicode, character in sortedhash(data) do
712            local symbol  = character.mathsymbol
713            local mset    = true
714            local class   = character.mathclass
715            local spec    = character.mathspec
716            local name    = character.mathname
717            local stretch = character.mathstretch
718            local group   = character.mathgroup
719            local meaning = character.mathmeaning
720            if symbol then
721                local other = data[symbol]
722                local class = other.mathclass
723                if class then
724                    local engine = toengineclass(class)
725                    if trace_defining then
726                        report(engine,family,unicode,symbol,group)
727                    end
728                    mset = setmathcharacter(engine,family,unicode,symbol,mset,group,meaning)
729                end
730                local spec = other.mathspec
731                if spec then
732                    for i=1,#spec do
733                        local m = spec[i]
734                        local class = m.class
735                        if class then
736                            local engine = toengineclass(class)
737                            -- todo: trace
738                            mset = setmathcharacter(engine,family,unicode,symbol,mset,group,meaning)
739                        end
740                    end
741                end
742            end
743            if spec then
744                local done = false
745                if class then
746                    if name then
747                        report_math("fatal error, conflicting mathclass and mathspec for %C",unicode)
748                        os.exit()
749                    else
750                        class = classes[class] or ordinary_class
751                        local engine = toengineclass(class)
752                        if trace_defining then
753                            report(engine,family,unicode,nil,group)
754                        end
755                        mset = setmathcharacter(engine,family,unicode,unicode,mset,group,meaning)
756                        done = true
757                    end
758                end
759                for i=1,#spec do
760                    local m       = spec[i]
761                    local name    = m.name
762                    local class   = m.class   or class
763                    local group   = m.group   or group
764                    local stretch = m.stretch or stretch
765                    local meaning = m.meaning or meaning
766                    if class then
767                        class = classes[class] or ordinary_class
768                    else
769                        class = ordinary_class
770                    end
771                    if class then
772                        local engine = toengineclass(class)
773                        if name then
774                            if trace_defining then
775                                report(engine,family,unicode,name,group)
776                            end
777                            setmathsymbol(name,engine,family,unicode,stretch,group,meaning)
778                        else
779                            name = (class == classes.ordinary or class == classes.digit) and "no name" -- character.adobename -- bad
780                            if name and trace_defining then
781                                report(engine,family,unicode,name,group)
782                            end
783                        end
784                        if not done then
785                            mset = setmathcharacter(engine,family,unicode,m.unicode or unicode,mset,group,meaning) -- see solidus
786                            done = true
787                        end
788                    end
789                end
790            else
791                if class then
792                    class = classes[class] or ordinary_class
793                else
794                    class = ordinary_class
795                end
796                if name ~= nil then
797                    local engine = toengineclass(class)
798                    if name == false then
799                        if trace_defining then
800                            report(engine,family,unicode,name,group)
801                        end
802                        mset = setmathcharacter(engine,family,unicode,unicode,mset,group,meaning)
803                    else
804                     -- if not name then
805                     --     name = character.contextname -- too dangerous, we loose textslash and a few more
806                     -- end
807                        if name then
808                            if trace_defining then
809                                report(engine,family,unicode,name,group)
810                            end
811                            if not group then
812                                if class == variable_class then
813                                 -- happens with greek where have a name but don't set a group .. somewhat messy
814                                    group = i_everygroup
815                                else
816                                 -- report(engine,family,unicode,name) -- character.adobename)
817                                end
818                            end
819                            setmathsymbol(name,engine,family,unicode,stretch,group,meaning)
820                        else
821                            if trace_defining then
822                                report(engine,family,unicode,"no name",group) -- character.adobename)
823                            end
824                        end
825                        mset = setmathcharacter(engine,family,unicode,unicode,mset,group,meaning)
826                    end
827                elseif class ~= ordinary_class then
828                    local engine = toengineclass(class)
829                    if trace_defining then
830                        report(engine,family,unicode,"no name",group) -- character.adobename)
831                    end
832                    mset = setmathcharacter(engine,family,unicode,unicode,mset,group,meaning)
833                end
834            end
835        end
836        --
837        if trace_defining then
838            logs.stopfilelogging()
839        end
840    end
841
842end
843
844-- needed for mathml analysis
845-- string with # > 1 are invalid
846-- we could cache
847
848do
849
850    local lpegmatch = lpeg.match
851    local utf8byte  = lpeg.patterns.utf8byte * lpeg.P(-1)
852
853    -- function somechar(c)
854    --     local b = lpegmatch(utf8byte,c)
855    --     return b and chardata[b]
856    -- end
857
858    local somechar = table.setmetatableindex(function(t,k)
859        if k then
860            local b = lpegmatch(utf8byte,k)
861            local v = b and chardata[b] or false
862            t[k] = v
863            return v
864        end
865    end)
866
867    local function utfmathclass(chr, default)
868        local cd = somechar[chr]
869        return cd and cd.mathclass or default or "unknown"
870    end
871
872    local function utfmathlimop(chr)
873        local cd = somechar[chr]
874        return cd and (cd.mathclass == "operator" or cd.mathclass == "integral") or false
875    end
876
877    local function utfmathaccent(chr,default,asked1,asked2)
878        local cd = somechar[chr]
879        if not cd then
880            return default or false
881        end
882        if asked1 and asked1 ~= "" then
883            local mc = cd.mathclass
884            if mc and (mc == asked1 or mc == asked2) then
885                return true
886            end
887            local ms = cd.mathspec
888            if not ms then
889                local mp = cd.mathparent
890                if mp then
891                    ms = chardata[mp].mathspec
892                end
893            end
894            if ms then
895                for i=1,#ms do
896                    local msi = ms[i]
897                    local mc = msi.class
898                    if mc and (mc == asked1 or mc == asked2) then
899                        return true
900                    end
901                end
902            end
903        else
904            local mc = cd.mathclass
905            if mc then
906                return accents[mc] or default or false
907            end
908            local ms = cd.mathspec
909            if ms then
910                for i=1,#ms do
911                    local msi = ms[i]
912                    local mc = msi.class
913                    if mc then
914                        return accents[mc] or default or false
915                    end
916                end
917            end
918        end
919        return default or false
920    end
921
922    local function utfmathstretch(chr,default) -- "h", "v", "b", ""
923        local cd = somechar[chr]
924        return cd and cd.mathstretch or default or ""
925    end
926
927    local function utfmathcommand(chr,default,asked1,asked2)
928        local cd = somechar[chr]
929        if not cd then
930            return default or ""
931        end
932        if asked1 then
933            local mn = cd.mathname
934            local mc = cd.mathclass
935            if mn and mc and (mc == asked1 or mc == asked2) then
936                return mn
937            end
938            local ms = cd.mathspec
939            if not ms then
940                local mp = cd.mathparent
941                if mp then
942                    ms = chardata[mp].mathspec
943                end
944            end
945            if ms then
946                for i=1,#ms do
947                    local msi = ms[i]
948                    local mn = msi.name
949                    if mn then
950                        local mc = msi.class
951                        if mc == asked1 or mc == asked2 then
952                            return mn
953                        end
954                    end
955                end
956            end
957        else
958            local mn = cd.mathname
959            if mn then
960                return mn
961            end
962            local ms = cd.mathspec
963            if ms then
964                for i=1,#ms do
965                    local msi = ms[i]
966                    local mn = msi.name
967                    if mn then
968                        return mn
969                    end
970                end
971            end
972        end
973        return default or ""
974    end
975
976    local function utfmathfiller(chr, default)
977        local cd = somechar[chr]
978        local cmd = cd and cd.mathfiller -- or cd.mathname
979        return cmd or default or ""
980    end
981
982    mathematics.utfmathclass   = utfmathclass
983    mathematics.utfmathstretch = utfmathstretch
984    mathematics.utfmathcommand = utfmathcommand
985    mathematics.utfmathfiller  = utfmathfiller
986    mathematics.utfmathaccent  = utfmathaccent
987
988    -- interfaced
989
990    implement {
991        name      = "utfmathclass",
992        public    = true,
993        actions   = { utfmathclass, context },
994        arguments = "argument"
995    }
996
997    implement {
998        name      = "utfmathstretch",
999        public    = true,
1000        actions   = { utfmathstretch, context },
1001        arguments = "argument"
1002    }
1003
1004    implement {
1005        name      = "utfmathcommand",
1006        public    = true,
1007        actions   = { utfmathcommand, context },
1008        arguments = "argument"
1009    }
1010
1011    implement {
1012        name      = "utfmathfiller",
1013        public    = true,
1014        actions   = { utfmathfiller, context },
1015        arguments = "argument"
1016    }
1017
1018    implement {
1019        name      = "utfmathcommandabove",
1020        public    = true,
1021        actions   = { utfmathcommand, context },
1022        arguments = { "argument", false, "'topaccent'","'over'" }
1023    }
1024
1025    implement {
1026        name      = "utfmathcommandbelow",
1027        public    = true,
1028        actions   = { utfmathcommand, context },
1029        arguments = { "argument", false, "'bottomaccent'","'under'" }
1030    }
1031
1032    implement {
1033        name      = "utfmathcommandfiller",
1034        public    = true,
1035        actions   = { utfmathfiller, context },
1036        arguments = "argument"
1037    }
1038
1039    -- todo: make this a helper:
1040
1041    implement {
1042        name      = "doifelseutfmathabove",
1043        public    = true,
1044        actions   = { utfmathaccent, ctx_doifelsesomething },
1045        arguments = { "argument", false, "'topaccent'", "'over'" }
1046    }
1047
1048    implement {
1049        name      = "doifelseutfmathbelow",
1050        public    = true,
1051        actions   = { utfmathaccent, ctx_doifelsesomething },
1052        arguments = { "argument", false, "'bottomaccent'", "'under'" }
1053    }
1054
1055    implement {
1056        name      = "doifelseutfmathaccent",
1057        public    = true,
1058        actions   = { utfmathaccent, ctx_doifelsesomething },
1059        arguments = "argument",
1060    }
1061
1062    implement {
1063        name      = "doifelseutfmathfiller",
1064        public    = true,
1065        actions   = { utfmathfiller, ctx_doifelsesomething },
1066        arguments = "argument",
1067    }
1068
1069    implement {
1070        name      = "doifelseutfmathlimop",
1071        public    = true,
1072        actions   = { utfmathlimop, ctx_doifelsesomething },
1073        arguments = "argument"
1074    }
1075
1076end
1077
1078do
1079
1080    -- 1: step 1
1081    -- 2: step 2
1082    -- 3: htdp * 1.33^n
1083    -- 4: size * 1.33^n
1084    -- 5: use lfg
1085
1086    implement {
1087        name      = "mathvariantslot",
1088        public    = true,
1089        usage     = "value",
1090        arguments = "2 integers",
1091        actions   = function(fam,n)
1092            local b = fontdata[getfontoffamily(fam)].bigslots
1093            if b then
1094                n = (n > #b and b[#b]) or b[n] or n
1095            end
1096            return integer_value, n
1097+ 1
1098        end
1099    }
1100
1101    -- will go away:
1102
1103    function mathematics.big(tfmdata,unicode,n,method)
1104        local t = tfmdata.characters
1105        local c = t[unicode]
1106        if c and n > 0 then
1107            if method == 1 or method == 2 or method == 5 then
1108                if method == 5 then
1109                    local b = tfmdata.bigslots
1110                    if b then
1111                        n = (n > #b and b[#b]) or b[n] or n
1112                    end
1113                elseif method == 2 then -- large steps
1114                    n = n * 2
1115                end
1116                local next = c.next
1117                while next do
1118                    if n <= 1 then
1119                        return next
1120                    else
1121                        n = n - 1
1122                        local tn = t[next].next
1123                        if tn then
1124                            next = tn
1125                        else
1126                            return next
1127                        end
1128                    end
1129                end
1130            elseif method >= 3 then
1131                local size = 1.33^n
1132                if method == 4 then
1133                    size = tfmdata.parameters.size * size
1134                else -- if method == 3 then
1135                    size = (c.height + c.depth) * size
1136                end
1137                local next = c.next
1138                while next do
1139                    local cn = t[next]
1140                    if (cn.height + cn.depth) >= size then
1141                        return next
1142                    else
1143                        local tn = cn.next
1144                        if tn then
1145                            next = tn
1146                        else
1147                            return next
1148                        end
1149                    end
1150                end
1151            end
1152        end
1153        return unicode
1154    end
1155
1156end
1157
1158do -- experimental, not stored in the format
1159
1160    local categories       = { }
1161    mathematics.categories = categories
1162
1163    local a_mathcategory   <const> = attributes.private("mathcategory")
1164    local a_mathstack      <const> = attributes.private("mathstack")
1165
1166    local functions        = storage.allocate()
1167    categories.functions   = functions
1168    local noffunctions     = 0
1169
1170    local function identify(kind,tag,method)
1171        local n = functions[tag]
1172        if n then
1173            n = n.index
1174        else
1175            n = noffunctions + 1 ---
1176            local t = {
1177                kind   = kind,
1178                tag    = tag,
1179                method = method,
1180                index  = n,
1181            }
1182            functions[n] = t
1183            functions[tag] = t
1184            noffunctions = n
1185        end
1186        return n
1187    end
1188
1189    implement {
1190        name      = "tagmfunctionlab", -- this one will be replaced by the next
1191        arguments = { "integer", "string", "string" },
1192        actions   = function(kind,tag,method)
1193            texsetattribute(a_mathcategory,identify(kind,tag,method))
1194        end
1195    }
1196
1197    implement {
1198        name      = "tagmfunctionlabattribute",
1199        usage     = "value",
1200        arguments = { "integer", "string", "string" },
1201        actions   = function(kind,tag,method)
1202            return integer_value, identify(kind,tag,method)
1203        end
1204    }
1205
1206    function mathematics.functiontype(n)
1207        local func = n and functions[n]
1208        local kind = func and func.kind or 0
1209        if kind == 1 then
1210            return "function"
1211        elseif kind == 2 then
1212            return "accent"
1213        elseif kind == 3 then
1214            return "fence"
1215        else
1216            return "unknown"
1217        end
1218    end
1219
1220end
1221
1222do
1223
1224    local list
1225
1226    function mathematics.resetattributes()
1227        if not list then
1228            list = { }
1229            for k, v in next, attributes.numbers do
1230                if find(k,"^math") then
1231                    list[#list+1] = v
1232                end
1233            end
1234        end
1235        for i=1,#list do
1236            texsetattribute(list[i],unsetvalue)
1237        end
1238    end
1239
1240end
1241
1242implement {
1243    name      = "resetmathattributes",
1244    public    = true,
1245    protected = true,
1246    actions   = mathematics.resetattributes
1247}
1248
1249-- weird to do this here but it's a side affect of math anyway
1250
1251implement {
1252    name     = "enableasciimode",
1253    onlyonce = true,
1254    actions  = resolvers.macros.enablecomment,
1255}
1256
1257implement {
1258    name      = "nofmathvariants",
1259    public    = true,
1260    usage     = "value",
1261    arguments = "integer",
1262    actions   = function(n)
1263        local char = fontchardata[getfontoffamily(0)]
1264        local data = char[n]
1265        local size = 1
1266        while data do
1267            local next = data.next
1268            if next then
1269                size = size + 1
1270                data = char[next]
1271            else
1272                break
1273            end
1274        end
1275        return integer_value, size
1276    end,
1277}
1278
1279implement {
1280    name      = "getmathvariant",
1281    public    = true,
1282    usage     = "value",
1283    arguments = "2 integers",
1284    actions   = function(m,n)
1285        local char = fontchardata[getfontoffamily(0)]
1286        local data = char[n]
1287        local slot = n
1288        if data then
1289            while data and m > 1 do
1290                local next = data.next
1291                if next then
1292                    m = m - 1
1293                    data = char[next]
1294                    slot = next
1295                else
1296                    break
1297                end
1298            end
1299        end
1300        return integer_value, slot
1301    end,
1302}
1303
1304implement {
1305    name      = "getmathcharone",
1306    public    = true,
1307    usage     = "value",
1308    arguments = "integer",
1309    actions   = function(n)
1310        local char = fontchardata[getfontoffamily(0)]
1311        local data = char[n]
1312        return integer_value, data and data.smaller or n
1313    end,
1314}
1315
1316implement {
1317    name      = "getmathchartwo",
1318    public    = true,
1319    usage     = "value",
1320    arguments = "integer",
1321    actions   = function(n)
1322        local char = fontchardata[getfontoffamily(0)]
1323        local data = char[n]
1324        local slot = data and data.smaller
1325        if slot then
1326            data = char[slot]
1327            n = slot
1328        end
1329        return integer_value, data and data.smaller or n
1330    end,
1331}
1332