if not modules then modules = { } end modules ['back-exp'] = {
    version   = 1.001,
    comment   = "companion to back-exp.mkiv",
    author    = "Hans Hagen, PRAGMA-ADE, Hasselt NL",
    copyright = "PRAGMA ADE / ConTeXt Development Team",
    license   = "see context related readme files"
}

-- See drawinglines.tex for some about the mathmnl namespace.

-- Todo: share properties more with tagged pdf (or the reverse)

-- Because we run into the 200 local limit we quite some do .. end wrappers .. not always
-- that nice but it has to be.

-- Experiments demonstrated that mapping to <div> and classes is messy because we have to
-- package attributes (some 30) into one set of (space seperatated but prefixed classes)
-- which only makes things worse .. so if you want something else, use xslt to get there.

-- language       -> only mainlanguage, local languages should happen through start/stoplanguage
-- tocs/registers -> maybe add a stripper (i.e. just don't flush entries in final tree)
-- footnotes      -> css 3
-- bodyfont       -> in styles.css

-- Because we need to look ahead we now always build a tree (this was optional in
-- the beginning). The extra overhead in the frontend is neglectable.
--
-- We can optimize the code ... currently the overhead is some 10% for xml + html so
-- there is no hurry.

-- todo: move critital formatters out of functions
-- todo: delay loading (apart from basic tag stuff)

-- problem : too many local variables

-- check setting __i__

-- In 2024 this module got updated a bit as part of the upgraded math features, which makes
-- sense as at that time it is some 15 years old. This time the musical timestamp is the
-- CD release of Dream Chaser by Rendezvous Point. (So whenever I got bored by exporting I
-- watched the Presence video on YT.)

local next, type, tonumber = next, type, tonumber
local sub, gsub, match = string.sub, string.gsub, string.match
local validstring = string.valid
local lpegmatch = lpeg.match
local utfchar, utfvalues, utflen = utf.char, utf.values, utf.len
local concat, merge, sort, setmetatableindex = table.concat, table.merge, table.sort, table.setmetatableindex
local sortedhash, sortedkeys = table.sortedhash, table.sortedkeys
local formatters = string.formatters
local todimen = number.todimen
local replacetemplate = utilities.templates.replace
local settings_to_array = utilities.parsers.settings_to_array
local settings_to_hash = utilities.parsers.settings_to_hash

local addsuffix, joinfile, nameonly, basename, filesuffix = file.addsuffix, file.join, file.nameonly, file.basename, file.suffix

local trace_export  = false  trackers.register  ("export.trace",         function(v) trace_export  = v end)
local trace_spacing = false  trackers.register  ("export.trace.spacing", function(v) trace_spacing = v end)
local trace_details = false  trackers.register  ("export.trace.details", function(v) trace_details = v end)

local less_state    = false  directives.register("export.lessstate",     function(v) less_state    = v end)
local show_comment  = true   directives.register("export.comment",       function(v) show_comment  = v end)
local only_images   = false  directives.register("export.images",        function(v) only_images   = v end)

-- maybe we will also support these:
--
-- local css_hyphens       = false  directives.register("export.css.hyphens",      function(v) css_hyphens      = v end)
-- local css_textalign     = false  directives.register("export.css.textalign",    function(v) css_textalign    = v end)
-- local css_bodyfontsize  = false  directives.register("export.css.bodyfontsize", function(v) css_bodyfontsize = v end)
-- local css_textwidth     = false  directives.register("export.css.textwidth",    function(v) css_textwidth    = v end)

local report_export     = logs.reporter("backend","export")

local nodes             = nodes
local attributes        = attributes

local variables         = interfaces.variables
local v_yes             <const> = variables.yes
local v_no              <const> = variables.no
local v_xml             <const> = variables.xml
local v_hidden          <const> = variables.hidden

local implement         = interfaces.implement

local tasks             = nodes.tasks
local fontchar          = fonts.hashes.characters
local fontquads         = fonts.hashes.quads

local texgetcount       = tex.getcount

local references        = structures.references
local structurestags    = structures.tags
local taglist           = structurestags.taglist
local specifications    = structurestags.specifications
local properties        = structurestags.properties
local locatedtag        = structurestags.locatedtag

structurestags.usewithcare = { }

local starttiming       = statistics.starttiming
local stoptiming        = statistics.stoptiming

local characterdata     = characters.data
local overloads         = fonts.mappings.overloads

-- todo: more locals (and optimize)

local exportversion     <const> = "0.36"
local mathmlns          <const> = "http://www.w3.org/1998/Math/MathML"
local contextns         <const> = "http://www.contextgarden.net/context/export" -- whatever suits
local cssnamespaceurl   <const> = "@namespace context url('%namespace%') ;"
local cssnamespace      <const> = "context|"
----- cssnamespacenop   <const> = "/* no namespace */"

local usecssnamespace   = false

local nofcurrentcontent = 0 -- so we don't free (less garbage collection)
local currentcontent    = { }
local currentnesting    = nil
local currentattribute  = nil
local last              = nil
local currentparagraph  = nil

local noftextblocks     = 0

----- hyphencode        = 0xAD
local hyphen            = utfchar(0xAD) -- todo: also emdash etc
local tagsplitter       = structurestags.patterns.splitter
----- colonsplitter     = lpeg.splitat(":")
----- dashsplitter      = lpeg.splitat("-")
local threshold         = 65536
local indexing          = false
local keephyphens       = false
local exportproperties  = false

local finetuning        = { }

local treestack         = { }
local nesting           = { }
local currentdepth      = 0

local wrapups           = { }

local tree              = { data = { }, fulltag == "root" } -- root
local roottree          = tree
local treehash          = { }
local extras            = { }
local checks            = { }
local fixes             = { }
local finalizers        = { }
local nofbreaks         = 0
local used              = { }
local exporting         = false
local restart           = false
local specialspaces     = { [0x20] = " "  }               -- for conversion
local somespace         = { [0x20] = true, [" "] = true } -- for testing
local entities          = { ["&"] = "&amp;", [">"] = "&gt;", ["<"] = "&lt;" }
local attribentities    = { ["&"] = "&amp;", [">"] = "&gt;", ["<"] = "&lt;", ['"'] = "quot;" }

local p_entity          = lpeg.replacer(entities) -- was: entityremapper = utf.remapper(entities)
local p_attribute       = lpeg.replacer(attribentities)
local p_escaped         = lpeg.patterns.xml.escaped

local f_tagid           = formatters["%s-%04i"]

-- local alignmapping = {
--     flushright = "right",
--     middle     = "center",
--     flushleft  = "left",
-- }

local exportlanguage = languages.exportlanguage

local defaultnature = "mixed" -- "inline"

setmetatableindex(used, function(t,k)
    if k then
        local v = { }
        t[k] = v
        return v
    end
end)

local f_entity    = formatters["&#x%X;"]
local f_attribute = formatters[" %s=%q"]
local f_property  = formatters[" %s%s=%q"]

setmetatableindex(specialspaces, function(t,k)
    local v = utfchar(k)
    t[k] = v
    entities[v] = f_entity(k)
    somespace[k] = true
    somespace[v] = true
    return v
end)

-- We removed (mathml) namespaces but the code can be found in the archive and in the
-- mkiv lua file. For the independent mathml see the older lmt file.

local mathtags = {
    msubsup       = "mathml",
    msub          = "mathml",
    msup          = "mathml",
    mn            = "mathml",
    mi            = "mathml",
    ms            = "mathml",
    mo            = "mathml",
    mc            = "mathml",
    mtext         = "mathml",
    mrow          = "mathml",
    mfrac         = "mathml",
    mroot         = "mathml",
    msqrt         = "mathml",
    munderover    = "mathml",
    munder        = "mathml",
    mover         = "mathml",
    merror        = "mathml",
    math          = "mathml",
    mrow          = "mathml",
    mtable        = "mathml",
    mtr           = "mathml",
    mtd           = "mathml",
    mfenced       = "mathml", -- no longer valid
    maction       = "mathml",
    mspace        = "mathml",
    mmultiscripts = "mathml",
}

local function attribute(key,value)
    if value and value ~= "" then
        return f_attribute(key,lpegmatch(p_attribute,value))
    else
        return ""
    end
end

-- todo: split class and real attributes so that we don't need this
-- privates hackery (and forget one)

local function setattribute(di,key,value,escaped)
    if value and value ~= "" then
        local a = di.attributes
        if escaped then
            value = lpegmatch(p_escaped,value)
        end
        if not a then
            di.attributes = { [key] = value }
        else
            a[key] = value
        end
    end
end

local listdata = { } -- this has to be done otherwise: each element can just point back to ...

function wrapups.hashlistdata()
    local c = structures.lists.collected
    for i=1,#c do
        local ci = c[i]
        local tag = ci.references.tag
        if tag then
            local m = ci.metadata
            local t = m.kind .. ">" .. tag -- todo: use internal (see strc-lst.lua where it's set)
            listdata[t] = ci
        end
    end
end

function structurestags.setattributehash(attr,key,value) -- public hash
    local specification = taglist[attr]
    if specification then
        specification[key] = value
    else
        -- some kind of error
    end
end

local usedstyles      = { }
local usedimages      = { }
local referencehash   = { } -- move ?
local destinationhash = { } -- move ?

structurestags.backend = {
    setattribute    = setattribute,
    extras          = extras,
    checks          = checks,
    fixes           = fixes,
    listdata        = listdata,
    finalizers      = finalizers,
    usedstyles      = usedstyles,
    usedimages      = usedimages,
    referencehash   = referencehash,
    destinationhash = destinationhash,
}

local namespacetemplate <const> = [[
/* %what% for file %filename% */

%cssnamespaceurl%
]]

do

local documenttemplate <const> = [[
:root {
	--margin: 2.5em;
}

document,
%namespace%div.document {
    font-family : TextNormal ;
    font-size   : %size% ;
    max-width   : calc(var(--margin) + %width%) ;
    text-align  : %align% ;
    hyphens     : %hyphens% ;
    zoom        : %zoom% ;
}

/* There is no real solution for boldening, 900 is not enough. */

math {
    font-family : MathNormal ;
}

math[data-lmtx-family="bold"] {
    font-family : MathNormal ;
	font-weight : 900 ;
}]]

local styletemplate <const> = [[
%element%[detail="%detail%"],
%namespace%div.%element%.%detail% {
    display      : inline ;
    font-style   : %style% ;
    font-variant : %variant% ;
    font-weight  : %weight% ;
    font-family  : %family% ;
    color        : %color% ;
}]]

    local numbertoallign = { [0] =
        "justify", ["0"] = "justify", [variables.normal    ] = "justify",
        "right",   ["1"] = "right",   [variables.flushright] = "right",
        "center",  ["2"] = "center",  [variables.middle    ] = "center",
        "left",    ["3"] = "left",    [variables.flushleft ] = "left",
    }

    function wrapups.allusedstyles(filename)
        local result = { replacetemplate(namespacetemplate, {
            what            = "styles",
            filename        = filename,
            namespace       = contextns,
         -- cssnamespaceurl = usecssnamespace and cssnamespaceurl or cssnamespacenop,
            cssnamespaceurl = cssnamespaceurl,
        },false,true) }
        --
        local bodyfont = finetuning.bodyfont
        local width    = finetuning.width
        local hyphen   = finetuning.hyphen
        local align    = finetuning.align
        local zoom     = finetuning.zoom
        local margin   = finetuning.margin
        --
     -- if not bodyfont then
     --     bodyfont = tex.getdimen("globalbodyfontsize")
     -- end
     -- if not width then
     --     width = tex.getdimen("textwidth")
     -- end
        if type(bodyfont) == "number" then
            bodyfont = todimen(bodyfont)
        else
            bodyfont = "12pt"
        end
        if type(width) == "number" then
            width = todimen(width) or "50em"
        else
            width = "50em"
        end
        if type(margin) == "number" then
            margin = todimen(margin) or "2.5em"
        else
            margin = "2.5em"
        end
        if hyphen == v_yes then
            hyphen = "manual"
        else
            hyphen = "auto"
        end
        if align then
            align = numbertoallign[align]
        end
        if not align then
            align = hyphen and "justify" or "inherited"
        end
        if not zoom then
            zoom = tex.sp("12pt")/tex.sp(bodyfont)
        end
        --
        result[#result+1] = replacetemplate(documenttemplate,{
            size    = bodyfont,
            width   = width,
            align   = align,
            hyphens = hyphen,
            zoom    = formatters["%0.3f"](zoom),
        })
        --
        local colorspecification = xml.css.colorspecification
        local fontspecification  = xml.css.fontspecification
        for element, details in sortedhash(usedstyles) do
            for detail, data in sortedhash(details) do
                local color = data.color
                local style = data.style
                local c = colorspecification(color)
                local s = structures.tags.backend.fontfaced(style)
                if not c then
                    c = "inherit"
                end
                if s and s.family and s.family ~= "" then
                    if not s.style   then s.style   = "normal" end
                    if not s.variant then s.variant = "normal" end
                    if not s.weight  then s.weight  = "normal" end
                else
                    s = fontspecification(style)
                    if not s.style   then s.style   = "inherit" end -- or just normal
                    if not s.variant then s.variant = "inherit" end -- or just normal
                    if not s.weight  then s.weight  = "inherit" end -- or just normal
                    if not s.family  then s.family  = "inherit" end -- or just normal
                end
                local detail = gsub(detail,"[^A-Za-z0-9]+","-")
                result[#result+1] = replacetemplate(styletemplate,{
                    namespace = usecssnamespace and cssnamespace or "",
                    element   = element,
                    detail    = detail,
                    style     = s.style,
                    variant   = s.variant,
                    weight    = s.weight,
                    family    = s.family,
                    color     = c,
                    display   = s.display and "block" or nil,
                })
            end
        end
        return concat(result,"\n\n")
    end

    function wrapups.allusedfonts(filename)
        local list, used = structures.tags.backend.tofontface(finetuning.fontfaces)
        local result = { replacetemplate(namespacetemplate, {
            what            = "fonts",
            filename        = filename,
            namespace       = contextns,
         -- cssnamespaceurl = usecssnamespace and cssnamespaceurl or cssnamespacenop,
            cssnamespaceurl = cssnamespaceurl,
        },false,true) }
        result[#result+1] = list
        result = concat(result,"\n\n")
        for k, v in sortedhash(used) do
            report_export("font face %s%s : %s",v[1],v[2],v[3])
        end
        return result
    end

end

do

local imagetemplate_1 <const> = [[
[image="%id%"]%hover% {
    display : block ;
    content : url('%url%') ;
    width   : %width% ;
    height  : %height% ;
}]]

local imagetemplate_2 <const> = [[
[image="%id%"]%hover% {
    display    : inline ;
    content    : url('%url%') ;
    width      : %width% ;
    height     : %height% ;
    margin-top : -%drop% ;
    top        : %drop% ;
    position   : relative ;
}]]

    local f_svgname = formatters["%s.svg"]
    local f_svgpage = formatters["%s-page-%s.svg"]
    local collected = { }

    local function usedname(name,page)
        if filesuffix(name) == "pdf" then
            -- temp hack .. we will have a remapper
            if page and page > 1 then
                name = f_svgpage(nameonly(name),page)
            else
                name = f_svgname(nameonly(name))
            end
        end
        local scheme = url.hasscheme(name)
        if not scheme or scheme == "file" then
            -- or can we just use the name ?
            return joinfile("../images",basename(url.filename(name)))
        else
            return name
        end
    end

    function wrapups.allusedimages(filename)
        local result = { replacetemplate(namespacetemplate, {
            what            = "images",
            filename        = filename,
            namespace       = contextns,
         -- cssnamespaceurl = usecssnamespace and cssnamespaceurl or "",
            cssnamespaceurl = cssnamespaceurl,
        },false,true) }
        local hover = (finetuning.images) and finetuning.images.hover
        for element, details in sortedhash(usedimages) do
            for detail, data in sortedhash(details) do
                local name  = data.name
                local page  = tonumber(data.page) or 1
                local drop  = data.drop
                local spec = {
                    element   = element,
                    id        = data.id,
                    name      = name,
                    page      = page,
                    url       = usedname(name,page),
                    width     = data.width,
                    height    = data.height,
                    drop      = drop,
                    used      = data.used,
                    namespace = usecssnamespace and cssnamespace or "",
                    hover     = hover and data.category == "formula" and ":hover" or "",
                }
                result[#result+1] = replacetemplate(
                    drop and imagetemplate_2 or imagetemplate_1,
                    spec
                )
                collected[detail] = spec
            end
        end
        return concat(result,"\n\n")
    end

    function wrapups.uniqueusedimages() -- todo: combine these two
        return collected
    end

end

--

properties.vspace = { export = "break",     nature = "display" }
----------------- = { export = "pagebreak", nature = "display" }

local function makebreaklist(list)
    nofbreaks = nofbreaks + 1
    local t = { }
    local l = list and list.taglist
    if l then
        for i=1,#list do
            t[i] = l[i]
        end
    end
    t[#t+1] = "break>" .. nofbreaks -- maybe no number or 0
    return { taglist = t }
end

local breakattributes = {
    type = "collapse"
}

local function makebreaknode(attributes) -- maybe no fulltag
    nofbreaks = nofbreaks + 1
    return {
        tg         = "break",
        fulltag    = "break>" .. nofbreaks,
        n          = nofbreaks,
        element    = "break",
        nature     = "display",
        attributes = attributes or nil,
     -- data       = { }, -- not needed
     -- attribute  = 0, -- not needed
     -- parnumber  = 0,
    }
end

do

    local fields = { "title", "subtitle", "author", "keywords", "url", "version" }

    local ignoredelements = false

    local function checkdocument(root)
        local data = root.data
        if data then
            for i=1,#data do
                local di = data[i]
                local tg = di.tg
                if tg == "noexport" then
                    local s = specifications[di.fulltag]
                    local u = s and s.userdata
                    if u then
                        local comment = u.comment
                        if comment then
                            di.element = "comment"
                            di.data = { { content = comment } }
                            u.comment = nil
                        else
                            data[i] = false
                        end
                    else
                        data[i] = false
                    end
                elseif di.content then
                    -- okay
                elseif tg == "ignore" then
                    di.element = ""
                    checkdocument(di)
                elseif ignoredelements and ignoredelements[tg] then
                    di.element = ""
                    checkdocument(di)
                else
                    checkdocument(di) -- new, else no noexport handling
                end
            end
        end
    end

    function extras.document(di,element,n,fulltag)
        local language = exportlanguage(texgetcount("mainlanguagenumber"))
        setattribute(di,"language",language)
        setattribute(di,"xml:lang",language)
        if not less_state then
            setattribute(di,"file",tex.jobname)
            setattribute(di,"date",os.fulltime())
            setattribute(di,"context",environment.version)
            setattribute(di,"version",exportversion)
            local identity = interactions.general.getidentity()
            for i=1,#fields do
                local key   = fields[i]
                local value = identity[key]
                if value and value ~= "" then
                    setattribute(di,key,value)
                end
            end
        end
        checkdocument(di)
    end

    implement {
        name      = "ignoretagsinexport",
        arguments = "string",
        actions   = function(list)
            for tag in string.gmatch(list,"[a-z]+") do
                if ignoredelements then
                    ignoredelements[tag] = true
                else
                    ignoredelements = { [tag] = true }
                end
            end
        end,
    }

end

-- flusher

do

    local f_detail                     = formatters[' detail="%s"']
    local f_chain                      = formatters[' chain="%s"']
    local f_index                      = formatters[' n="%s"']
    local f_spacing                    = formatters['<c p="%s">%s</c>']

    local f_empty_inline               = formatters["<%s/>"]
    local f_empty_mixed                = formatters["%w<%s/>\n"]
    local f_empty_display              = formatters["\n%w<%s/>\n"]
    local f_empty_inline_attr          = formatters["<%s%s/>"]
    local f_empty_mixed_attr           = formatters["%w<%s%s/>"]
    local f_empty_display_attr         = formatters["\n%w<%s%s/>\n"]

    local f_begin_inline               = formatters["<%s>"]
    local f_begin_mixed                = formatters["%w<%s>"]
    local f_begin_display              = formatters["\n%w<%s>\n"]
    local f_begin_inline_attr          = formatters["<%s%s>"]
    local f_begin_mixed_attr           = formatters["%w<%s%s>"]
    local f_begin_display_attr         = formatters["\n%w<%s%s>\n"]

    local f_end_inline                 = formatters["</%s>"]
    local f_end_mixed                  = formatters["</%s>\n"]
    local f_end_display                = formatters["%w</%s>\n"]

    local f_begin_inline_comment       = formatters["<!-- %s --><%s>"]
    local f_begin_mixed_comment        = formatters["%w<!-- %s --><%s>"]
    local f_begin_display_comment      = formatters["\n%w<!-- %s -->\n%w<%s>\n"]
    local f_begin_inline_attr_comment  = formatters["<!-- %s --><%s%s>"]
    local f_begin_mixed_attr_comment   = formatters["%w<!-- %s --><%s%s>"]
    local f_begin_display_attr_comment = formatters["\n%w<!-- %s -->\n%w<%s%s>\n"]

    local f_comment_begin_inline       = formatters["<!-- begin %s -->"]
    local f_comment_begin_mixed        = formatters["%w<!-- begin %s -->"]
    local f_comment_begin_display      = formatters["\n%w<!-- begin %s -->\n"]

    local f_comment_end_inline         = formatters["<!-- end %s -->"]
    local f_comment_end_mixed          = formatters["<!-- end %s -->\n"]
    local f_comment_end_display        = formatters["%w<!-- end %s -->\n"]

    local f_metadata_begin             = formatters["\n%w<metadata>\n"]
    local f_metadata                   = formatters["%w<metavariable name=%q>%s</metavariable>\n"]
    local f_metadata_end               = formatters["%w</metadata>\n"]

    local function attributes(a)
        local r = { }
        local n = 0
        for k, v in next, a do
            n = n + 1
            r[n] = f_attribute(k,tostring(v)) -- tostring because of %q
        end
        sort(r)
        return concat(r,"")
    end

    local function properties(a)
        local r = { }
        local n = 0
        for k, v in next, a do
            n = n + 1
            r[n] = f_property(exportproperties,k,tostring(v)) -- tostring because of %q
        end
        sort(r)
        return concat(r,"")
    end

    local depth  = 0
    local inline = 0

    local function emptytag(result,element,nature,di) -- currently only break but at some point
        local a = di.attributes                       -- we might add detail etc
        if a then -- happens seldom
            if nature == "display" then
                result[#result+1] = f_empty_display_attr(depth,element,attributes(a))
            elseif nature == "mixed" then
                result[#result+1] = f_empty_mixed_attr(depth,element,attributes(a))
            else
                result[#result+1] = f_empty_inline_attr(element,attributes(a))
            end
        else
            if nature == "display" then
                result[#result+1] = f_empty_display(depth,element)
            elseif nature == "mixed" then
                result[#result+1] = f_empty_mixed(depth,element)
            else
                result[#result+1] = f_empty_inline(element)
            end
        end
    end

 -- local function stripspaces(di)
 --     local d = di.data
 --     local n = #d
 --     local m = 0
 --     for i=1,n do
 --         local di = d[i]
 --         if di.tg then
 --             m = m + 1
 --             d[m] = di
 --         end
 --     end
 --     for i=n,m+1,-1 do
 --         d[i] = nil
 --     end
 -- end
 --
 -- -- simpler:

    local function stripspaces(di)
        local d = di.data
        for i=1,#d do
            local di = d[i]
            if not di.tg then
                di.content = ""
            end
        end
    end

    local function begintag(result,element,nature,di,skip)
        local index         = di.n
        local fulltag       = di.fulltag
        local specification = specifications[fulltag] or { } -- we can have a dummy
        local comment       = di.comment
        local detail        = specification.detail
        if skip == "comment" then
            if show_comment then
                if nature == "inline" or inline > 0 then
                    result[#result+1] = f_comment_begin_inline(element)
                    inline = inline + 1
                elseif nature == "mixed" then
                    result[#result+1] = f_comment_begin_mixed(depth,element)
                    depth = depth + 1
                    inline = 1
                else
                    result[#result+1] = f_comment_begin_display(depth,element)
                    depth = depth + 1
                end
            end
        elseif skip then
            -- ignore
        else

            local n = 0
            local r = { } -- delay this
            if detail then
                detail = gsub(detail,"[^A-Za-z0-9]+","-")
                specification.detail = detail -- we use it later in for the div
                n = n + 1
                r[n] = f_detail(detail)
            end
            local parents = specification.parents
            if parents then
                parents = gsub(parents,"[^A-Za-z0-9 ]+","-")
                specification.parents = parents -- we use it later in for the div
                n = n + 1
                r[n] = f_chain(parents)
            end
            if indexing and index then
                n = n + 1
                r[n] = f_index(index)
            end
            --
            local extra = extras[element]
            if extra then
                extra(di,element,index,fulltag)
            end
            --
            if di.record then
                stripspaces(di)
            end
            --
            if exportproperties then
                local p = specification.userdata
                if not p then
                    -- skip
                elseif exportproperties == v_yes then
                    n = n + 1
                    r[n] = attributes(p)
                else
                    n = n + 1
                    r[n] = properties(p)
                end
            end
            local a = di.attributes
            if a then
                if trace_spacing then
                    a.p = di.parnumber or 0
                end
                n = n + 1
                r[n] = attributes(a)
            elseif trace_spacing then
                n = n + 1
                r[n] = attributes { p = di.parnumber or 0 }
            end
            if n == 0 then
                if nature == "inline" or inline > 0 then
                    if show_comment and comment then
                        result[#result+1] = f_begin_inline_comment(comment,element)
                    else
                        result[#result+1] = f_begin_inline(element)
                    end
                    inline = inline + 1
                elseif nature == "mixed" then
                    if show_comment and comment then
                        result[#result+1] = f_begin_mixed_comment(depth,comment,element)
                    else
                        result[#result+1] = f_begin_mixed(depth,element)
                    end
                    depth = depth + 1
                    inline = 1
                else
                    if show_comment and comment then
                        result[#result+1] = f_begin_display_comment(depth,comment,depth,element)
                    else
                        result[#result+1] = f_begin_display(depth,element)
                    end
                    depth = depth + 1
                end
            else
                r = concat(r,"",1,n)
                if nature == "inline" or inline > 0 then
                    if show_comment and comment then
                        result[#result+1] = f_begin_inline_attr_comment(comment,element,r)
                    else
                        result[#result+1] = f_begin_inline_attr(element,r)
                    end
                    inline = inline + 1
                elseif nature == "mixed" then
                    if show_comment and comment then
                        result[#result+1] = f_begin_mixed_attr_comment(depth,comment,element,r)
                    else
                        result[#result+1] = f_begin_mixed_attr(depth,element,r)
                    end
                    depth = depth + 1
                    inline = 1
                else
                    if show_comment and comment then
                        result[#result+1] = f_begin_display_attr_comment(depth,comment,depth,element,r)
                    else
                        result[#result+1] = f_begin_display_attr(depth,element,r)
                    end
                    depth = depth + 1
                end
            end
        end
        used[element][detail or ""] = { nature, specification.parents }  -- for template css
        -- also in last else ?
        local metadata = specification.metadata
        if metadata and next(metadata) then
            result[#result+1] = f_metadata_begin(depth)
            for k, v in sortedhash(metadata) do
                if v ~= "" then
                    result[#result+1] = f_metadata(depth+1,k,lpegmatch(p_entity,v))
                end
            end
            result[#result+1] = f_metadata_end(depth)
        end
    end

    local function endtag(result,element,nature,di,skip)
        if skip == "comment" then
            if show_comment then
                if nature == "display" and (inline == 0 or inline == 1) then
                    depth = depth - 1
                    result[#result+1] = f_comment_end_display(depth,element)
                    inline = 0
                elseif nature == "mixed" and (inline == 0 or inline == 1) then
                    depth = depth - 1
                    result[#result+1] = f_comment_end_mixed(element)
                    inline = 0
                else
                    inline = inline - 1
                    result[#result+1] = f_comment_end_inline(element)
                end
            end
        elseif skip then
            -- ignore
        else
            if nature == "display" and (inline == 0 or inline == 1) then
                depth = depth - 1
                result[#result+1] = f_end_display(depth,element)
                inline = 0
            elseif nature == "mixed" and (inline == 0 or inline == 1) then
                depth = depth - 1
                result[#result+1] = f_end_mixed(element)
                inline = 0
            else
                inline = inline - 1
                result[#result+1] = f_end_inline(element)
            end
        end
    end

    local function wrapupmath(di)
        -- We arrive here twice which is a bit waste of time but for now
        -- we just do it. The first time we have no blob set anyway.
        local a = di.attributes
        local order = a and (a["data-lmtx-blob"] or a["blob"])
        if order then
            local mth = mathematics.getmathblob("xml",order)
            local txt = mathematics.gettextblob("xml","en",order)
            if mth then
                mth = match(mth,"<math[^>]*>(.*)</math>")
            end
            if txt and txt ~= "" then
             -- local a = di.attributes
                if a then
                    a["data-lmtx-meaning"]  = txt
                else
                    di.attributes = {
                        ["data-lmtx-meaning"] = txt,
                    }
                end
            end
            return mth
        end
    end

    local function flushtree(result,data,nature)
        local nofdata = #data
        for i=1,nofdata do
            local di = data[i]
            if not di then -- hm, di can be string
                -- whatever
            else
                local content = di.content
             -- also optimize for content == "" : trace that first
                if content then
                    -- already has breaks
                    local content = lpegmatch(p_entity,content)
                    if i == nofdata and sub(content,-1) == "\n" then -- move check
                        -- can be an end of line in par but can also be the last line
                        if trace_spacing then
                            result[#result+1] = f_spacing(di.parnumber or 0,sub(content,1,-2))
                        else
                            result[#result+1] = sub(content,1,-2)
                        end
                        result[#result+1] = " "
                    else
                        if trace_spacing then
                            result[#result+1] = f_spacing(di.parnumber or 0,content)
                        else
                            result[#result+1] = content
                        end
                    end
                elseif not di.collapsed then -- ignore collapsed data (is appended, reconstructed par)
                    local element = di.element
                    if not element then
                        -- skip
                    elseif element == "break" then -- or element == "pagebreak" -- todo: use empty flag
                        emptytag(result,element,nature,di)
                    elseif element == "mspace" then -- todo: use empty flag
-- can this still happen
                        emptytag(result,element,nature,di)
                    elseif element == "mprescripts" then -- todo: use empty flag
-- can this still happen
                        emptytag(result,element,nature,di) -- -why has nature to be set
                    elseif element == "" or di.skip == "ignore" then --
                        -- skip
                    else
                        local mth = element == "math" and wrapupmath(di)
                        if di.before then
                            flushtree(result,di.before,nature)
                        end
                        local natu = di.nature
                        local skip = di.skip
                        if di.breaknode then
                            -- this never happens as we don seem to set this field
                            emptytag(result,"break","display",di)
                        end
                        begintag(result,element,natu,di,skip)
                        if mth and mth ~= "" then
                            result[#result+1] = mth -- the stripped one
                        else
                            flushtree(result,di.data,natu)
                        end
                        endtag(result,element,natu,di,skip)
                        if di.after then
                            flushtree(result,di.after,nature)
                        end
                    end
                else
--                     local element = di.element
--                     if element == "mspace" then -- todo: use empty flag
--                         emptytag(result,element,nature,di)
--                     end
                end
            end
        end
    end

    local function breaktree(tree,parent,parentelement) -- also removes double breaks
        local data = tree.data
        if data then
            local nofdata = #data
            local prevelement
            local prevnature
            local prevparnumber
            local newdata = { }
            local nofnewdata = 0
            for i=1,nofdata do
                local di = data[i]
                if not di then
                    -- skip
                elseif di.skip == "ignore" then
                    -- skip (new)
                elseif di.tg == "ignore" then
                    -- skip (new)
                elseif di.content then
                    if di.samepar then
                        prevparnumber = false
                    else
                        local parnumber = di.parnumber
                        if prevnature == "inline" and prevparnumber and prevparnumber ~= parnumber then
                            nofnewdata = nofnewdata + 1
                            if trace_spacing then
                                newdata[nofnewdata] = makebreaknode { type = "a", p = prevparnumber, n = parnumber }
                            else
                                newdata[nofnewdata] = makebreaknode()
                            end
                        end
                        prevelement = nil
                        prevparnumber = parnumber
                    end
                    prevnature = "inline"
                    nofnewdata = nofnewdata + 1
                    newdata[nofnewdata] = di
                elseif not di.collapsed then
                    local element = di.element
                    if element == "break" then -- or element == "pagebreak"
                        if prevelement == "break" then
                            di.element = ""
                        end
                        prevelement = element
                        prevnature = "display"
                        nofnewdata = nofnewdata + 1
                        newdata[nofnewdata] = di
                    elseif element == "" or di.skip == "ignore" then
                        -- skip
                    else
                        if di.samepar then
                            prevnature    = "inline"
                            prevparnumber = false
                        else
                            local nature = di.nature
                            local parnumber = di.parnumber
                            if prevnature == "inline" and nature == "inline" and prevparnumber and prevparnumber ~= parnumber then
                                nofnewdata = nofnewdata + 1
                                if trace_spacing then
                                    newdata[nofnewdata] = makebreaknode { type = "b", p = prevparnumber, n = parnumber }
                                else
                                    newdata[nofnewdata] = makebreaknode()
                                end
                            end
                            prevnature = nature
                            prevparnumber = parnumber
                        end
                        prevelement = element
                        breaktree(di,tree,element)
                        nofnewdata = nofnewdata + 1
                        newdata[nofnewdata] = di
                    end
                else
                    if di.samepar then
                        prevnature    = "inline"
                        prevparnumber = false
                    else
                        local nature = di.nature
                        local parnumber = di.parnumber
                        if prevnature == "inline" and nature == "inline" and prevparnumber and prevparnumber ~= parnumber then
                            nofnewdata = nofnewdata + 1
                            if trace_spacing then
                                newdata[nofnewdata] = makebreaknode { type = "c", p = prevparnumber, n = parnumber }
                            else
                                newdata[nofnewdata] = makebreaknode()
                            end
                        end
                        prevnature = nature
                        prevparnumber = parnumber
                    end
                    nofnewdata = nofnewdata + 1
                    newdata[nofnewdata] = di
                end
            end
            tree.data = newdata
        end
    end

    -- also tabulaterow reconstruction .. maybe better as a checker
    -- i.e cell attribute

    local function showtree(data,when,where)
        if data then
            for i=1,#data do
                local d = data[i]
                if type(d) == "table" and d.element then
                    print(when,where,i,d.element,d.parnumber or 0)
                end
            end
        end
    end

    local function collapsetree(tree)
     -- showtree(data,"before","collapse")
     -- for tag, trees in sortedhash(treehash) do
        for tag, trees in next, treehash do
            local d = trees[1].data
            if d then
                local nd = #d
                if nd > 0 then
                    for i=2,#trees do
                        local currenttree = trees[i]
                        local currentdata = currenttree.data
                        local currentpar  = currenttree.parnumber
                        local previouspar = trees[i-1].parnumber
                        currenttree.collapsed = true
                        -- is the next ok?
                        if previouspar == 0 or not (di and di.content) then
                            previouspar = nil -- no need anyway so no further testing needed
                        end
                        for j=1,#currentdata do
                            local cd = currentdata[j]
                            if not cd or cd == "" then
                                -- skip
                            elseif cd.skip == "ignore" then
                                -- skip
                            elseif cd.content then
                                if not currentpar then
                                    -- add space ?
                                elseif not previouspar then
                                    -- add space ?
                                elseif currentpar ~= previouspar then
                                    nd = nd + 1
                                    if trace_spacing then
                                        d[nd] = makebreaknode { type = "d", p = previouspar, n = currentpar }
                                    else
                                        d[nd] = makebreaknode()
                                    end
                                end
                                previouspar = currentpar
                                nd = nd + 1
                                d[nd] = cd
                            else
                                nd = nd + 1
                                d[nd] = cd
                            end
                            currentdata[j] = false
                        end
                    end
                end
            end
        end
     -- showtree(data,"after","collapse")
    end

    local function finalizetree(tree)
     -- showtree(data,"before","finalize")
        for _, finalizer in next, finalizers do
            finalizer(tree)
        end
     -- showtree(data,"after","finalize")
    end

    local function indextree(tree)
        local data = tree.data
        if data then
         -- showtree(data,"before","index")
            local n, new = 0, { }
            for i=1,#data do
                local d = data[i]
                if not d then
                    -- skip
                elseif d.content then
                    n = n + 1
                    new[n] = d
                elseif not d.collapsed then
                    n = n + 1
                    d.__i__ = n
                    d.__p__ = tree
                    indextree(d)
                    new[n] = d
                end
            end
            tree.data = new
         -- showtree(new,"after","index")
        end
    end

    local function checktree(tree)
        local data = tree.data
        if data then
         -- showtree(data,"before","check")
            for i=1,#data do
                local d = data[i]
                if type(d) == "table" then
                    local tg = d.tg
                    if tg then
                        local check = checks[tg]
                        if check then
                            check(d,data,i)
                        end
                    end
                    checktree(d) -- so parts can pass twice
                end
            end
         -- showtree(data,"after","check")
        end
    end

    local function fixtree(tree)
        local data = tree.data
        if data then
         -- showtree(data,"before","fix")
            for i=1,#data do
                local d = data[i]
                if type(d) == "table" then
                    local tg = d.tg
                    if tg then
                        local fix = fixes[tg]
                        if fix then
                            fix(d,data,i)
                        end
                    end
                    fixtree(d) -- so parts can pass twice
                end
            end
         -- showtree(data,"after","fix")
        end
    end

    wrapups.flushtree    = flushtree
    wrapups.breaktree    = breaktree
    wrapups.collapsetree = collapsetree
    wrapups.finalizetree = finalizetree
    wrapups.indextree    = indextree
    wrapups.checktree    = checktree
    wrapups.fixtree      = fixtree

end

-- collector code

local function push(fulltag,depth)
    local tg, n, detail, element, nature, record
    local specification = specifications[fulltag]
    if specification then
        tg     = specification.tagname
        n      = specification.tagindex
        detail = specification.detail
    elseif not fulltag then
        report_export("%w<%s trigger=%q n=%q paragraph=%q index=%q detail=%q>",
            currentdepth-1,tg,n,currentattribute or 0,currentparagraph or 0,"error",detail)
        return
    else
        -- a break (more efficient if we don't store those in specifications)
        tg, n = lpegmatch(tagsplitter,fulltag)
        n = tonumber(n) -- to tonumber in tagsplitter
    end
    local p = properties[tg]
    if p then
        element = p.export or tg
        nature  = p.nature or "inline" -- defaultnature
        record  = p.record
    end
    local treedata = tree.data
    if not treedata then
        report_export("%w<%s trigger=%q n=%q paragraph=%q index=%q detail=%q>",
            currentdepth-1,tg,n,currentattribute or 0,currentparagraph or 0,"error",detail)
        return
    end
    local t = { -- maybe we can use the tag table
        tg        = tg,
        fulltag   = fulltag,
        detail    = detail,
        n         = n, -- already a number
        element   = element,
        nature    = nature,
        data      = { },
        attribute = currentattribute,
        parnumber = currentparagraph,
        record    = record, -- we can consider storing properties
    }
    treedata[#treedata+1] = t
    currentdepth = currentdepth + 1
    nesting[currentdepth] = fulltag
    treestack[currentdepth] = tree
    if trace_export then
        if detail and detail ~= "" then
            report_export("%w<%s trigger=%q n=%q paragraph=%q index=%q detail=%q>",
                currentdepth-1,tg,n,currentattribute or 0,currentparagraph or 0,#treedata,detail)
        else
            report_export("%w<%s trigger=%q n=%q paragraph=%q index=%q>",
                currentdepth-1,tg,n,currentattribute or 0,currentparagraph or 0,#treedata)
        end
    end
    tree = t
    if tg == "break" then
        -- no need for this
    else
        local h = treehash[fulltag]
        if h then
            h[#h+1] = t
        else
            treehash[fulltag] = { t }
        end
    end
end

local function pop()
    if currentdepth > 0 then
        local top = nesting[currentdepth]
        tree = treestack[currentdepth]
        currentdepth = currentdepth - 1
        if trace_export then
            if top then
                report_export("%w</%s>",currentdepth,match(top,"[^>]+"))
            else
                report_export("</BAD>")
            end
        end
    else
        report_export("%w<!-- too many pops -->",currentdepth)
    end
end

local function continueexport()
    if nofcurrentcontent > 0 then
        if trace_export then
            report_export("%w<!-- injecting pagebreak space -->",currentdepth)
        end
        nofcurrentcontent = nofcurrentcontent + 1
        currentcontent[nofcurrentcontent] = " " -- pagebreak
    end
end

local function pushentry(current)
    if not current then
        -- bad news
        return
    end
    current = current.taglist
    if not current then
        -- even worse news
        return
    end
    if restart then
        continueexport()
        restart = false
    end
    local newdepth = #current
    local olddepth = currentdepth
    if trace_export then
        report_export("%w<!-- moving from depth %s to %s (%s) -->",currentdepth,olddepth,newdepth,current[newdepth])
    end
    if olddepth <= 0 then
        for i=1,newdepth do
            push(current[i],i)
        end
    else
        local difference
        if olddepth < newdepth then
            for i=1,olddepth do
                if current[i] ~= nesting[i] then
                    difference = i
                    break
                end
            end
        else
            for i=1,newdepth do
                if current[i] ~= nesting[i] then
                    difference = i
                    break
                end
            end
        end
        if difference then
            for i=olddepth,difference,-1 do
                pop()
            end
            for i=difference,newdepth do
                push(current[i],i)
            end
        elseif newdepth > olddepth then
            for i=olddepth+1,newdepth do
                push(current[i],i)
            end
        elseif newdepth < olddepth then
            for i=olddepth,newdepth,-1 do
                pop()
            end
        elseif trace_export then
            report_export("%w<!-- staying at depth %s (%s) -->",currentdepth,newdepth,nesting[newdepth] or "?")
        end
    end
    return olddepth, newdepth
end

local function pushcontent(oldparagraph,newparagraph)
    if nofcurrentcontent > 0 then
        if oldparagraph then
            if currentcontent[nofcurrentcontent] == "\n" then
                if trace_export then
                    report_export("%w<!-- removing newline -->",currentdepth)
                end
                nofcurrentcontent = nofcurrentcontent - 1
            end
        end
        local content = concat(currentcontent,"",1,nofcurrentcontent)
-- print(content,currentattribute)
        if content == "" then
            -- omit; when oldparagraph we could push, remove spaces, pop
        elseif somespace[content] and oldparagraph then
            -- omit; when oldparagraph we could push, remove spaces, pop
-- elseif not tree or not tree.data then
        else
            local olddepth, newdepth
            local list = taglist[currentattribute]
            if list then
                olddepth, newdepth = pushentry(list)
            end
            if tree then
                local td = tree.data
                local nd = #td
                td[nd+1] = { parnumber = oldparagraph or currentparagraph, content = content }
                if trace_export then
                    report_export("%w<!-- start content with length %s -->",currentdepth,utflen(content))
                    report_export("%w%s",currentdepth,(gsub(content,"\n","\\n")))
                    report_export("%w<!-- stop content -->",currentdepth)
                end
                if olddepth then
                    for i=newdepth-1,olddepth,-1 do
                        pop()
                    end
                end
            end
        end
        nofcurrentcontent = 0
    end
    if oldparagraph then
        pushentry(makebreaklist(currentnesting))
        if trace_export then
            report_export("%w<!-- break added between paragraph %a and %a -->",currentdepth,oldparagraph,newparagraph)
        end
    end
end

local function finishexport()
    if trace_export then
        report_export("%w<!-- start finalizing -->",currentdepth)
    end
    if nofcurrentcontent > 0 then
        if somespace[currentcontent[nofcurrentcontent]] then
            if trace_export then
                report_export("%w<!-- removing space -->",currentdepth)
            end
            nofcurrentcontent = nofcurrentcontent - 1
        end
        pushcontent()
    end
    for i=currentdepth,1,-1 do
        pop()
    end
    currentcontent = { } -- we're nice and do a cleanup
    if trace_export then
        report_export("%w<!-- stop finalizing -->",currentdepth)
    end
end

-- inserts ?

local collectresults  do -- too many locals otherwise

    local nodecodes          = nodes.nodecodes
    local gluecodes          = nodes.gluecodes
    local listcodes          = nodes.listcodes
    local whatsitcodes       = nodes.whatsitcodes

    local subtypes           = nodes.subtypes

    local userkern_code      <const> = nodes.kerncodes.userkern

    local hlist_code         <const> = nodecodes.hlist
    local vlist_code         <const> = nodecodes.vlist
    local glyph_code         <const> = nodecodes.glyph
    local glue_code          <const> = nodecodes.glue
    local kern_code          <const> = nodecodes.kern
    local disc_code          <const> = nodecodes.disc
    local whatsit_code       <const> = nodecodes.whatsit
    local par_code           <const> = nodecodes.par

    local userskip_code      <const> = gluecodes.userskip
    local rightskip_code     <const> = gluecodes.rightskip
    local parfillskip_code   <const> = gluecodes.parfillskip
    local spaceskip_code     <const> = gluecodes.spaceskip
    local xspaceskip_code    <const> = gluecodes.xspaceskip
    local intermathskip_code <const> = gluecodes.intermathskip

    local linelist_code      <const> = listcodes.line

    local userdefinedwhatsit_code  <const> = whatsitcodes.userdefined

    local privateattribute = attributes.private

    local a_image          <const> = privateattribute('image')
    local a_reference      <const> = privateattribute('reference')
    local a_destination    <const> = privateattribute('destination')
    local a_characters     <const> = privateattribute('characters')
    local a_exportstatus   <const> = privateattribute('exportstatus')
    local a_tagged         <const> = privateattribute('tagged')
    local a_taggedpar      <const> = privateattribute("taggedpar")
    local a_textblock      <const> = privateattribute("textblock")

    local inline_mark      <const> = nodes.pool.userids["margins.inline"]

    local nuts             = nodes.nuts

    local getnext          = nuts.getnext
    local getdisc          = nuts.getdisc
    local getlist          = nuts.getlist
    local getid            = nuts.getid
    local getattrs         = nuts.getattrs
    local getattr          = nuts.getattr
    local setattr          = nuts.setattr -- maybe use properties
    local isglyph          = nuts.isglyph
    local getkern          = nuts.getkern
    local getwidth         = nuts.getwidth
    local getclass         = nuts.getclass
    local getdiscpart      = nuts.getdiscpart

    local startofpar       = nuts.startofpar

    local nexthlist        = nuts.traversers.hlist
    local nextnode         = nuts.traversers.node

    local automatic_code   <const> = tex.glyphdisccodes.automatic
    local syllable_code    <const> = tex.glyphdisccodes.syllable

    local function addtomaybe(maybewrong,c,paragraph,ap,case)
        if trace_export then
            report_export("%w<!-- possible paragraph (%i,%i) mixup at %C case %i -->",currentdepth,paragraph or 0,ap or 0,c,case)
        else
            local s = formatters["%C"](c)
            if maybewrong then
                maybewrong[#maybewrong+1] = s
            else
                maybewrong = { s }
            end
            return maybewrong
        end
    end

    local function showmaybe(maybewrong)
        if not trace_export then
--             report_export("fuzzy paragraph: % t",maybewrong)
        end
    end

    local function showdetail(n,id,subtype)
        local a = getattr(n,a_tagged)
        local t = taglist[a]
        local c = nodecodes[id]
        local s = subtypes[id][subtype]
        if a and t then
            report_export("node %a, subtype %a, tag %a, element %a, tree '% t'",c,s,a,t.tagname,t.taglist)
        else
            report_export("node %a, subtype %a, untagged",c,s)
        end
    end

    local function collectresults(head,list,pat,pap) -- is last used (we also have currentattribute)
        local p
        local paragraph
        local maybewrong
        local pid
        local isdisc = false
        for n, id, subtype in nextnode, head do
            if trace_details then
                showdetail(n,id,subtype)
            end
            if id == glyph_code then
                local c, f = isglyph(n)
                local at, ap = getattrs(n,a_tagged,a_taggedpar)
                if not at then
                    at = pat
                end
                if not at then
                 -- we need to tag the pagebody stuff as being valid skippable
                 --
                 -- report_export("skipping character: %C (no attribute)",n.char)
                elseif at == 0 then
                    -- skip (needs checking)
                elseif at < 1 then
                    -- skip (needs checking)
                else
                    if last ~= at then
                        local tl = taglist[at]
                        if not ap then
                            ap = pap
                        end
-- if paragraph and (not ap or ap < paragraph) then
--     maybewrong = addtomaybe(maybewrong,c,paragraph,ap,1)
-- end
                        tl.class = getclass(n)
                        pushcontent()
                        currentnesting   = tl
                        currentparagraph = ap
                        currentattribute = at
                        last = at
                        pushentry(currentnesting)
                        if trace_export then
                            report_export("%w<!-- processing glyph %C tagged %a -->",currentdepth,c,at)
                        end
                        -- We need to intercept this here; maybe I will also move this
                        -- to a regular setter at the tex end.
                        local r, d = getattrs(n,a_reference,a_destination)
                        if r then
                            local t = tl.taglist
                            referencehash[t[#t]] = r -- fulltag
                        end
                        if d then
                            local t = tl.taglist
                            destinationhash[t[#t]] = d -- fulltag
                        end
                        --
                    elseif last then
                        -- we can consider tagging the pars (lines) in the parbuilder but then we loose some
                        -- information unless we inject a special node (but even then we can run into nesting
                        -- issues)
                        if not ap then
                            ap = pap
                        end
                        if ap ~= currentparagraph then
                            pushcontent(currentparagraph,ap)
                            pushentry(currentnesting)
                            currentattribute = last
                            currentparagraph = ap
                        end
-- if paragraph and (not ap or ap < paragraph) then
--     maybewrong = addtomaybe(maybewrong,c,paragraph,ap,2)
-- end
                        if trace_export then
                            report_export("%w<!-- processing glyph %C tagged %a -->",currentdepth,c,last)
                        end
                    else
                        if trace_export then
                            report_export("%w<!-- processing glyph %C tagged %a -->",currentdepth,c,at)
                        end
                    end
                    local s = getattr(n,a_exportstatus)
                    if s then
                        c = s
                    end
                    if c == 0 or c == 0xFFFD then
                        if trace_export then
                            report_export("%w<!-- skipping glyph %U -->",currentdepth,c)
                        end
                    elseif c == 0x20 then
                        local a = getattr(n,a_characters)
                        nofcurrentcontent = nofcurrentcontent + 1
                        if a then
                            if trace_export then
                                report_export("%w<!-- turning last space into special space %U -->",currentdepth,a)
                            end
                            currentcontent[nofcurrentcontent] = specialspaces[a] -- special space
                        else
                            currentcontent[nofcurrentcontent] = " "
                        end
                        isdisc = false
                    else
                        local fc = fontchar[f]
                        if fc then
                            fc = fc and fc[c]
                            if fc then
                                local dcode, dafter, dtype = getdiscpart(n)
                                local u = fc.unicode
                                if u == 0 or u == 0xFFFD then
                                    -- ignore (can make disappear)
                                    isdisc = false
                                elseif u == 0x2D then
                                    nofcurrentcontent = nofcurrentcontent + 1
                                    currentcontent[nofcurrentcontent] = "-"
                                    isdisc = dtype == automatic_code
                                else
                                    if keephyphens and dafter == syllable_code then
                                        nofcurrentcontent = nofcurrentcontent + 1
                                        currentcontent[nofcurrentcontent] = hyphen
                                    end
                                    if type(u) == "table" then
                                        for i=1,#u do
                                            nofcurrentcontent = nofcurrentcontent + 1
                                            currentcontent[nofcurrentcontent] = utfchar(u[i])
                                        end
                                    else
                                        nofcurrentcontent = nofcurrentcontent + 1
                                        currentcontent[nofcurrentcontent] = utfchar(u or c)
                                    end
                                    isdisc = false
                                end
                            elseif c > 0 then
                                nofcurrentcontent = nofcurrentcontent + 1
                                currentcontent[nofcurrentcontent] = utfchar(c)
                                isdisc = false
                            else
                                -- we can have -1 as side effect of an explicit hyphen (unless we expand)
                             -- isdisc = false
                            end
                        elseif c > 0 then
                            nofcurrentcontent = nofcurrentcontent + 1
                            currentcontent[nofcurrentcontent] = utfchar(c)
                            isdisc = false
                        else
                            -- we can have -1 as side effect of an explicit hyphen (unless we expand)
                         -- isdisc = false
                        end
                    end
                end
            elseif id == glue_code then
                -- we need to distinguish between hskips and vskips
                local ca, a = getattrs(n,a_characters,a_tagged)
                if ca == 0 then
                    -- skip this one ... already converted special character (node-acc)
                elseif ca then
                    if not a then
                        a = pat
                    end
                    if a then
                        local c = specialspaces[ca]
                        if last ~= a then
                            local tl = taglist[a]
                            if trace_export then
                                report_export("%w<!-- processing space glyph %U tagged %a case 1 -->",currentdepth,ca,a)
                            end
                            pushcontent()
                            currentnesting = tl
                            currentparagraph = getattr(n,a_taggedpar) or pap
                            currentattribute = a
                            last = a
                            pushentry(currentnesting)
                            -- no reference check (see above)
                        elseif last then
                            local ap = getattr(n,a_taggedpar) or pap
                            if ap ~= currentparagraph then
                                pushcontent(currentparagraph,ap)
                                pushentry(currentnesting)
                                currentattribute = last
                                currentparagraph = ap
                            end
                            if trace_export then
                                report_export("%w<!-- processing space glyph %U tagged %a case 2 -->",currentdepth,ca,last)
                            end
                        end
                        -- if somespace[currentcontent[nofcurrentcontent]] then
                        --     if trace_export then
                        --         report_export("%w<!-- removing space -->",currentdepth)
                        --     end
                        --     nofcurrentcontent = nofcurrentcontent - 1
                        -- end
                        nofcurrentcontent = nofcurrentcontent + 1
                        currentcontent[nofcurrentcontent] = c
                        isdisc = false
                    end
                elseif subtype == userskip_code then
                    if getwidth(n) > threshold then
                        if last and not somespace[currentcontent[nofcurrentcontent]] then
                            local a = getattr(n,a_tagged) or pat
                            if a == last then
                                if trace_export then
                                    report_export("%w<!-- injecting spacing 5a -->",currentdepth)
                                end
                                nofcurrentcontent = nofcurrentcontent + 1
                                currentcontent[nofcurrentcontent] = " "
                                isdisc = false
                            elseif a then
                                -- e.g LOGO<space>LOGO
                                if trace_export then
                                    report_export("%w<!-- processing glue > threshold tagged %s becomes %s -->",currentdepth,last,a)
                                end
                                pushcontent()
                                if trace_export then
                                    report_export("%w<!-- injecting spacing 5b -->",currentdepth)
                                end
                                last = a
                                nofcurrentcontent = nofcurrentcontent + 1
                                currentcontent[nofcurrentcontent] = " "
                                isdisc = false
                                currentnesting = taglist[last]
                                pushentry(currentnesting)
                                currentattribute = last
                            end
                        end
                    end
                elseif subtype == spaceskip_code or subtype == xspaceskip_code then
                    if not somespace[currentcontent[nofcurrentcontent]] then
                        local a = getattr(n,a_tagged) or pat
                        if a == last then
                            if trace_export then
                                report_export("%w<!-- injecting spacing 7 (stay in element) -->",currentdepth)
                            end
                            nofcurrentcontent = nofcurrentcontent + 1
                            currentcontent[nofcurrentcontent] = " "
                            isdisc = false
                        else
                            if trace_export then
                                report_export("%w<!-- injecting spacing 7 (end of element) -->",currentdepth)
                            end
                            last = a
                            pushcontent()
                            nofcurrentcontent = nofcurrentcontent + 1
                            currentcontent[nofcurrentcontent] = " "
                            isdisc = false
                            currentnesting = taglist[last]
                            pushentry(currentnesting)
                            currentattribute = last
                        end
                    end
                elseif subtype == intermathskip_code then
                    -- put this as attribute when it differs, maybe more ... check mathml
                elseif subtype == rightskip_code then
                    -- a line
                    if nofcurrentcontent > 0 then
                        local r = currentcontent[nofcurrentcontent]
                        if r == hyphen then
                            if not keephyphens then
                                nofcurrentcontent = nofcurrentcontent - 1
                                isdisc = false
                            end
                        elseif isdisc then
                            -- nasty
                        elseif pid == disc_code then
                            -- go on .. tricky: we should mark the glyhs as coming from a disc
                        elseif not somespace[r] then
                            local a = getattr(n,a_tagged) or pat
                            if a == last then
                                if trace_export then
                                    report_export("%w<!-- injecting spacing 1 (end of line, stay in element) -->",currentdepth)
                                end
                                nofcurrentcontent = nofcurrentcontent + 1
                                currentcontent[nofcurrentcontent] = " "
                            else
                                if trace_export then
                                    report_export("%w<!-- injecting spacing 1 (end of line, end of element) -->",currentdepth)
                                end
                                last = a
                                pushcontent()
                                nofcurrentcontent = nofcurrentcontent + 1
                                currentcontent[nofcurrentcontent] = " "
                                isdisc = false
                                currentnesting = taglist[last]
                                pushentry(currentnesting)
                                currentattribute = last
                            end
                        end
                    end
                elseif subtype == parfillskip_code then
                    -- deal with paragraph endings (crossings) elsewhere and we quit here
                    -- as we don't want the rightskip space addition
                    if maybewrong then
                        showmaybe(maybewrong)
                    end
--                     return
                end
            elseif id == hlist_code or id == vlist_code then
                local ai = getattr(n,a_image)
                if ai then
                    local at = getattr(n,a_tagged) or pat
-- print(ai,at)
                    if nofcurrentcontent > 0 then
                        pushcontent()
                        pushentry(currentnesting) -- ??
                    end
                    pushentry(taglist[at]) -- has an index, todo: flag empty element
                    if trace_export then
                        report_export("%w<!-- processing image tagged %a -->",currentdepth,last)
                    end
                    last = nil
                    currentparagraph = nil
                else
                    -- we need to determine an end-of-line
                    local list = getlist(n)
                    if list then
                        -- todo: no par checking needed in math
                        local at = getattr(n,a_tagged) or pat
                        collectresults(list,n,at)
                    end
                end
            elseif id == kern_code then
                if subtype == userkern_code then
                    local kern = getkern(n)
                    if kern > 0 then
                        local a = getattr(n,a_tagged) or pat
                        local t = taglist[a]
                        if not t or t.tagname ~= "ignore" then -- maybe earlier on top)
                            local limit = threshold
                            if p then
                                local c, f = isglyph(p)
                                if c then
                                    limit = fontquads[f] / 4
                                end
                            end
                            if kern > limit then
                                if last and not somespace[currentcontent[nofcurrentcontent]] then
                                 -- local a = getattr(n,a_tagged) or pat
                                    if a == last then
                                        if not somespace[currentcontent[nofcurrentcontent]] then
                                            if trace_export then
                                                report_export("%w<!-- injecting spacing 8 (kern %p) -->",currentdepth,kern)
                                            end
                                            nofcurrentcontent = nofcurrentcontent + 1
                                            currentcontent[nofcurrentcontent] = " "
                                            isdisc = false
                                        end
                                    elseif a then
                                        -- e.g LOGO<space>LOGO
                                        if trace_export then
                                            report_export("%w<!-- processing kern, threshold %p, tag %s => %s -->",currentdepth,limit,last,a)
                                        end
                                        last = a
                                        pushcontent()
                                        if trace_export then
                                            report_export("%w<!-- injecting spacing 9 (kern %p) -->",currentdepth,kern)
                                        end
                                        nofcurrentcontent = nofcurrentcontent + 1
                                        currentcontent[nofcurrentcontent] = " "
                                        isdisc = false
                                     -- currentnesting = taglist[last]
                                        currentnesting = t
                                        pushentry(currentnesting)
                                        currentattribute = last
                                    end
                                end
                            end
                        end
                    end
                end
            elseif id == whatsit_code then
                -- todo (lmtx)
                if subtype == userdefinedwhatsit_code then
                    -- similar to images, see above
                    local at = getattr(n,a_tagged)
                    if nofcurrentcontent > 0 then
                        pushcontent()
                        pushentry(currentnesting) -- ??
                    end
                    pushentry(taglist[at])
                    if trace_export then
                        report_export("%w<!-- processing anchor tagged %a",currentdepth,last)
                    end
                    last = nil
                    currentparagraph = nil
                end
            elseif id == par_code then
                if startofpar(n) then
                    paragraph = getattr(n,a_taggedpar)
                end
            elseif id == disc_code then
                -- very unlikely because we stripped them
                local pre, post, replace = getdisc(n)
                if keephyphens then
                    if pre and not getnext(pre) and isglyph(pre) == 0xAD then -- hyphencode then
                        nofcurrentcontent = nofcurrentcontent + 1
                        currentcontent[nofcurrentcontent] = hyphen
                        isdisc = false
                    end
                end
                if replace then
                    collectresults(replace,nil)
                end
            end
            p   = n
            pid = id
        end
        if maybewrong then
            showmaybe(maybewrong)
        end
    end

    local enabled = true

    updaters.register("tagging.state.disable",function() enabled = false end)
    updaters.register("tagging.state.enable", function() enabled = true  end)

    -- maybe also some fast enable/disable stack

    function nodes.handlers.export(head) -- hooks into the page builder
        if enabled then
            starttiming(treehash)
            if trace_export then
                report_export("%w<!-- start flushing page -->",currentdepth)
            end
         -- continueexport()
            restart = true
            collectresults(head)
            if trace_export then
                report_export("%w<!-- stop flushing page -->",currentdepth)
            end
            stoptiming(treehash)
        end
        return head
    end

    local c_tagparcounter <const> = tex.iscount("tagparcounter")

    function nodes.handlers.checkparcounter(p,mode)
        setattr(p,a_taggedpar,texgetcount(c_tagparcounter) + 1)
        return p
    end

    -- needs checking!

    function builders.paragraphs.tag(head)
        noftextblocks = noftextblocks + 1
        for n, subtype in nexthlist, head do
            if subtype == linelist_code then
                setattr(n,a_textblock,noftextblocks)
         -- elseif subtype == glue_code or subtype == kern_code then -- weird, no list
         --     setattr(n,a_textblock,0)
            end
        end
        return false
    end

end

do

    local xmlcollected  = xml.collected
    local xmlsetcomment = xml.setcomment

local xmlpreamble_nop = [[
<?xml version="1.0" encoding="UTF-8" standalone="%standalone%" ?>
]]

local xmlpreamble_yes = [[
<?xml version="1.0" encoding="UTF-8" standalone="%standalone%" ?>

<!--

    input filename   : %filename%
    processing date  : %date%
    context version  : %contextversion%
    exporter version : %exportversion%

-->

]]

    local flushtree = wrapups.flushtree

    local function wholepreamble(standalone,nocomment)
        return replacetemplate(nocomment and xmlpreamble_nop or xmlpreamble_yes, {
            standalone     = standalone and "yes" or "no",
            filename       = tex.jobname,
            date           = os.fulltime(),
            contextversion = environment.version,
            exportversion  = exportversion,
        })
    end


local csspreamble = [[
<?xml-stylesheet type="text/css" href="%filename%" ?>
]]

local cssheadlink = [[
<link type="text/css" rel="stylesheet" href="%filename%" />
]]

-- great, these suggested values attributes ... maybe we should just drop this
-- mathjax and accept suboptimal rendering

local mathmlheadscript = [[
<script
    type="text/javascript"
    id="MathJax-script"
    async="async"
    src="https://cdn.jsdelivr.net/npm/mathjax@3/es5/mml-chtml.js">
</script>
]]

    local function allusedstylesheets(cssfiles,files,path,extra)
        local done   = { }
        local result = { }
        local extras = { }
        for i=1,#cssfiles do
            local cssfile = cssfiles[i]
            if type(cssfile) ~= "string" then
                -- error
            elseif cssfile == "export-example.css" then
                -- ignore
            elseif not done[cssfile] then
                cssfile = joinfile(path,basename(cssfile))
                report_export("adding css reference '%s'",cssfile)
                files[#files+1]   = cssfile
                result[#result+1] = replacetemplate(csspreamble, { filename = cssfile })
                extras[#extras+1] = replacetemplate(cssheadlink, { filename = cssfile })
                done[cssfile]     = true
            end
        end
        if extra then
            extras[#extras+1] = extra
        end
        return concat(result), concat(extras)
    end

local elementtemplate <const> = [[
/* element="%element%" detail="%detail%" chain="%chain%" */

%element%,
%namespace%div.%element% {
    display: %display% ;
}]]

local detailtemplate <const> = [[
/* element="%element%" detail="%detail%" chain="%chain%" */

%element%[detail=%detail%],
%namespace%div.%element%.%detail% {
    display: %display% ;
}]]

-- <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.1 plus MathML 2.0 plus SVG 1.1//EN" "http://www.w3.org/2002/04/xhtml-math-svg/xhtml-math-svg.dtd" >

local htmltemplate <const> = [[
%preamble%

<html xmlns="http://www.w3.org/1999/xhtml"%?mathmlns: xmlns:m="%mathmlns%" lang="%language%" xml:lang="language%" ?%>

    <head>

        <meta charset="utf-8"/>

        <title>%title%</title>

%style%

    </head>
    <body>
        <div class="document" xmlns="http://www.pragma-ade.com/context/export">

<div class="warning">Rendering can be suboptimal because there is no default/fallback css loaded.</div>

%body%

        </div>
    </body>
</html>
]]

    local displaymapping = {
        inline  = "inline",
        display = "block",
        mixed   = "inline",
    }

    local function allusedelements(filename)
        local result = { replacetemplate(namespacetemplate, {
            what            = "template",
            filename        = filename,
            namespace       = contextns,
         -- cssnamespaceurl = usecssnamespace and cssnamespaceurl or "",
            cssnamespaceurl = cssnamespaceurl,
        },false,true) }
        for element, details in sortedhash(used) do
            if mathtags[element] then
                -- skip math
            else
                for detail, what in sortedhash(details) do
                    local nature  = what[1] or "display"
                    local chain   = what[2]
                    local display = displaymapping[nature] or "block"
                    if detail == "" then
                        result[#result+1] = replacetemplate(elementtemplate, {
                            element   = element,
                            display   = display,
                            chain     = chain,
                            namespace = usecssnamespace and namespace or "",
                        })
                    else
                        result[#result+1] = replacetemplate(detailtemplate, {
                            element   = element,
                            display   = display,
                            detail    = detail,
                            chain     = chain,
                            namespace = usecssnamespace and cssnamespace or "",
                        })
                    end
                end
            end
        end
        return concat(result,"\n\n")
    end

    local function allcontent(tree,nocheck,final)
        local result = { }
        local data   = tree.data
        if nocheck then
            -- maybe mathml
        else
            -- we need to get rid of crap and also now need to get rid of "documentpart"
            -- which is needed for tagged pdf
            local d = { }
            for i=1,#data do
                local di = data[i]
                if di.tg == "document" then
                    local d = di.data
                    for i=1,#d do
                        local ddi = d[i]
                        if ddi.tg == "documentpart" then
                            di.data = ddi.data
                            break
                        end
                    end
                    break
                end
            end
        end
if final then
    -- maybe strip 2..#
end
        flushtree(result,tree.data,"display") -- we need to collect images
        -- no need to lpeg .. fast enough
        local r = result[1]
        if r then
            result[1] = gsub(result[1],"^%s+","")
            result[#result] = gsub(result[#result],"%s+$","")
            result = concat(result)
            result = gsub(result,"\n *\n","\n")
            result = gsub(result,"\n +([^< ])","\n%1")
            return result
        else
            -- inspect(result)
        end
    end

    -- local xhtmlpreamble = [[
    --     <!DOCTYPE html PUBLIC
    --         "-//W3C//DTD XHTML 1.1 plus MathML 2.0 plus SVG 1.1//EN"
    --         "http://www.w3.org/2002/04/xhtml-math-svg/xhtml-math-svg.dtd"
    --     >
    -- ]]

    local function cleanxhtmltree(xmltree)
        if xmltree then
            local implicits = { }
            local explicits = { }
            local overloads = { }
            for e in xmlcollected(xmltree,"*") do
                local at = e.at
                if at then
                    local explicit = at.explicit
                    local implicit = at.implicit
                    if explicit then
                        if not explicits[explicit] then
                            explicits[explicit] = true
                            at.id = explicit
                            if implicit then
                                overloads[implicit] = explicit
                            end
                        end
                    else
                        if implicit and not implicits[implicit] then
                            implicits[implicit] = true
                            at.id = "aut:" .. implicit
                        end
                    end
                end
            end
            for e in xmlcollected(xmltree,"*") do
                local at = e.at
                if at then
                    local internal = at.internal
                    local location = at.location
                    if internal then
                        if location then
                            local explicit = overloads[location]
                            if explicit then
                                at.href = "#" .. explicit
                            else
                                at.href = "#aut:" .. internal
                            end
                        else
                            at.href = "#aut:" .. internal
                        end
                    else
                        if location then
                            at.href = "#" .. location
                        else
                            local url = at.url
                            if url then
                                at.href = url
                            else
                                local file = at.file
                                if file then
                                    at.href = file
                                end
                            end
                        end
                    end
                end
            end
            return xmltree
        else
            return xml.convert('<?xml version="1.0"?>\n<error>invalid xhtml tree</error>')
        end
    end

    -- maybe the reverse: be explicit about what is permitted

    local private = {
        destination     = true,
        prefix          = true,
        reference       = true,
        --
        id              = true,
        href            = true,
        --
        implicit        = true,
        explicit        = true,
        --
        url             = true,
        file            = true,
        internal        = true,
        location        = true,
        --
        name            = true, -- image name
        used            = true, -- image name
        page            = true, -- image name
        width           = true,
        height          = true,
        --
        image           = true,
        exported        = true,
        alt             = true, -- or what
        --
        descriptiontext = true,
        alternativetext = true,
        --
        n               = true, -- formula number
    }

    local addclicks   = true
    local f_onclick   = formatters[ [[location.href='%s']] ]

    local p_cleanid   = lpeg.replacer { [":"] = "-" }
    local p_cleanhref = lpeg.Cs(lpeg.P("#") * p_cleanid)

    local p_splitter  = lpeg.Ct ( (
        lpeg.Carg(1) * lpeg.C((1-lpeg.P(" "))^1) / function(d,s) if not d[s] then d[s] = true return s end end
      * lpeg.P(" ")^0 )^1 )


    local classes = setmetatableindex(function(t,k)
        local v = concat(lpegmatch(p_splitter,k,1,{})," ")
        t[k] = v
        return v
    end)

    local function makeclass(tg,at)
        local detail     = at.detail
        local chain      = at.chain
        local extra      = nil
        local classes    = { }
        local nofclasses = 0
        at.detail        = nil
        at.chain         = nil
        for k, v in next, at do
            if not private[k] then
                nofclasses = nofclasses + 1
                classes[nofclasses] = k .. "-" .. v
            end
        end
        if detail and detail ~= "" then
            if chain and chain ~= "" then
                if chain ~= detail then
                    extra = classes[tg .. " " .. chain .. " " .. detail]
                elseif tg ~= detail then
                    extra = detail
                end
            elseif tg ~= detail then
                extra = detail
            end
        elseif chain and chain ~= "" then
            if tg ~= chain then
                extra = chain
            end
        end
        -- in this order
        if nofclasses > 0 then
            sort(classes)
            classes = concat(classes," ")
            if extra then
                return tg .. " " .. extra .. " " .. classes
            else
                return tg .. " " .. classes
            end
        else
            if extra then
                return tg .. " " .. extra
            else
                return tg
            end
        end
    end

    -- Some elements are not supported (well) in css so we need to retain them. For
    -- instance, tablecells have no colspan so basically that renders css table div
    -- elements quite useless. A side effect is that we nwo can have conflicts when
    -- we mix in with other html (as there is no reset). Of course, when it eventually
    -- gets added, there is a change then that those not using the div abstraction
    -- will be rediculed.
    --
    -- a table tr td th thead tbody tfoot

    local crappycss = {
        table     = "table", tabulate      = "table",
        tablehead = "thead", tabulatehead  = "thead",
        tablebody = "tbody", tabulatebody  = "tbody",
        tablefoot = "tfoot", tabulatefoot  = "tfoot",
        tablerow  = "tr",    tabulaterow   = "tr",
        tablecell = "td",    tabulatecell  = "td",
    }

    local cssmapping = false

    directives.register("export.nativetags", function(v)
        cssmapping = v and crappycss or false
    end)

    local function remap(specification,source,target)
        local comment = nil -- share comments
        for c in xmlcollected(source,"*") do
            if not c.special then
                local tg = c.tg
             -- local ns = c.ns
                local at = c.at
                if tg == "math" then
                    at["xmlns"] = mathmlns
                    c.ns = ""
                elseif mathtags[tg] then
                    -- mathml
                else
                    local dt = c.dt
                    local nt = #dt
                    if nt == 0 or (nt == 1 and dt[1] == "") then
                        if comment then
                            c.dt = comment
                        else
                            xmlsetcomment(c,"empty")
                            comment = c.dt
                        end
                    end
                    local class = nil
                    local label = nil
                    local image = at.image
                    if tg == "document" then
                        at.href   = nil
                        at.detail = nil
                        at.chain  = nil
                    elseif tg == "metavariable" then
                        label = at.name
                        at.detail = "metaname-" .. label
                        class = makeclass(tg,at)
                    else
                        class = makeclass(tg,at)
                    end
                    local id   = at.id
                    local href = at.href
                    local attr = nil
                    if id then
                        id = lpegmatch(p_cleanid, id) or id
                        if href then
                            href = lpegmatch(p_cleanhref,href) or href
                            attr = {
                                class   = class,
                                id      = id,
                                href    = href,
                                onclick = addclicks and f_onclick(href) or nil,
                            }
                        else
                            attr = {
                                class = class,
                                id    = id,
                            }
                        end
                    else
                        if href then
                            href = lpegmatch(p_cleanhref,href) or href
                            attr = {
                                class   = class,
                                href    = href,
                                onclick = addclicks and f_onclick(href) or nil,
                            }
                        else
                            attr = {
                                class = class,
                            }
                        end
                    end
                    if image then
                        local alt = at and at.descriptiontext or ""
                        attr.image = image
                        attr.alt   = alt ~= "" and alt or nil
                    end
                    c.at = attr
                    if label then
                        attr.label = label
                    end
                    c.tg = cssmapping and cssmapping[tg] or "div"
                end
            end
        end
    end

 -- local cssfile = nil  directives.register("backend.export.css", function(v) cssfile = v end)

    local embedfile = false  directives.register("export.embed",function(v) embedfile = v end)

    local justexport = nodes.handlers.export

    local function wrapuptree(tree)
        wrapups.fixtree(tree)
        wrapups.collapsetree(tree)
        wrapups.indextree(tree)
        wrapups.checktree(tree)
        wrapups.breaktree(tree)
        wrapups.finalizetree(tree)
        --
        wrapups.hashlistdata()
        --
    end

    local function locate(tree,simple,level)
        if tree then
            if tree.tg == simple then
                return tree.__p__
            end
            local data = tree.data
            if data then
                for i=1,#data do
                    local d = locate(data[i],simple,level+1)
                    if d then
                        return d
                    end
                end
            end
        end
    end

    local function localexport(head,simple)
        starttiming(treehash)

        local saved_treestack    = treestack    ; treestack    = { }
        local saved_nesting      = nesting      ; nesting      = { }
        local saved_currentdepth = currentdepth ; currentdepth = 0
        local saved_tree         = tree         ; tree         = { data = { }, fulltag == "root" } -- root
        local saved_roottree     = roottree     ; roottree     = tree
        local saved_treehash     = treehash     ; treehash     = { }
        local saved_nofbreaks    = nofbreaks    ; nofbreaks    = 0
        local saved_show_comment = show_comment ; show_comment = false

local saved_nofcurrentcontent = nofcurrentcontent ; nofcurrentcontent = 0
local saved_currentcontent    = currentcontent    ; currentcontent    = { }
local saved_currentnesting    = currentnesting    ; currentnesting    = nil
local saved_currentattribute  = currentattribute  ; currentattribute  = nil
local saved_last              = last              ; last              = nil
local saved_currentparagraph  = currentparagraph  ; currentparagraph  = nil

        justexport(head)
        finishexport()
        wrapuptree(tree)

        local result

        if simple then
            local d = locate(tree,simple,1)
            if d then
                result = allcontent(d,true)
            end
        else
            result = concat {
                wholepreamble(true),
                allcontent(tree),
            }
        end

        treestack    = saved_treestack
        nesting      = saved_nesting
        currentdepth = saved_currentdepth
        tree         = saved_tree
        roottree     = saved_roottree
        treehash     = saved_treehash
        nofbreaks    = saved_nofbreaks
        show_comment = saved_show_comment

nofcurrentcontent = saved_nofcurrentcontent
currentcontent    = saved_currentcontent
currentnesting    = saved_currentnesting
currentattribute  = saved_currentattribute
last              = saved_last
currentparagraph  = saved_currentparagraph

        stoptiming(treehash)

        return result

    end

    structurestags.localexport = localexport

    function structures.tags.exportbox(n,filename,buffername)
        local list = nodes.nuts.getbox(n)
        if n then
            local e = localexport(list)
            if filename and filename ~= "" then
                io.savedata(filename,e)
            elseif buffername then
                buffers.assign(buffername == interfaces.variables.yes and "" or buffername,e)
            else
                return e
            end
        end
    end

    interfaces.implement {
        name      = "exportbox",
        arguments = { "integer", "string", "string" },
        actions   = structures.tags.exportbox
    }

    function structurestags.finishexport()

        if only_images then
            exporting = false
        end

        if exporting then
            exporting = false
        else
            return
        end

        local onlyxml = finetuning.export == v_xml

        starttiming(treehash)
        --
        finishexport()
        --
        report_export("")
        if onlyxml then
            report_export("exporting xml, no other files")
        else
            report_export("exporting xml, xhtml, html and css files")
        end
        report_export("")
        --
        wrapuptree(tree)
        --
        local exportxml   = true
        local exportxhtml = true
        local exporthtml  = true
        local useextra    = true -- compatibility for now
        --
        if finetuning.output == "xml" then
            exporthtml  = false
            exportxhtml = false
            useextra    = false
        elseif finetuning.output == "xhtml" then
            exportxml   = false
            exporthtml  = false
            useextra    = false
        elseif finetuning.output == "html" then
            exportxml   = false
            exportxhtml = false
            useextra    = false
        end
        --
        local askedname = finetuning.file
        local pathname  = finetuning.path
        --
        -- normally we use a dedicated subpath:
        --
        -- ./jobname-export
        -- ./jobname-export/images
        -- ./jobname-export/styles
        -- ./jobname-export/jobname-export.xml
        -- ./jobname-export/jobname-export.xhtml
        -- ./jobname-export/jobname-export.html
        -- ./jobname-export/jobname-specification.lua
        -- ./jobname-export/styles/jobname-defaults.css
        -- ./jobname-export/styles/jobname-fonts.css
        -- ./jobname-export/styles/jobname-styles.css
        -- ./jobname-export/styles/jobname-images.css
        -- ./jobname-export/styles/jobname-templates.css

        if type(askedname) ~= "string" or askedname == "" then
            askedname = tex.jobname
        end
        if type(pathname) ~= "string" or pathname == "" then
            pathname = false
        end

        local usedname  = nameonly(askedname)
        local basepath  = usedname .. "-export"

if not useextra then
    basepath = "."
end

        local imagepath = joinfile(basepath,"images")
        local stylepath = joinfile(basepath,"styles")

        if pathname then
            basepath  = joinfile(pathname,basepath)
            imagepath = joinfile(pathname,imagepath)
            stylepath = joinfile(pathname,stylepath)
        end

        local function validpath(what,pathname)
            if lfs.isdir(pathname) then
                report_export("using existing %s path %a",what,pathname)
                return pathname
            end
            lfs.mkdirs(pathname)
            if lfs.isdir(pathname) then
                report_export("using cretated %s path %a",what,basepath)
                return pathname
            else
                report_export("unable to create %s path %a",what,basepath)
                return false
            end
        end

        if not (validpath("export",basepath )
            and validpath("images",imagepath)
            and validpath("styles",stylepath)) then
            return
        end

        -- we're now on the dedicated export subpath so we can't clash names
        --
        -- a xhtml suffix no longer seems to be work well with browsers

        local xmlfilebase           = addsuffix(usedname .. (useextra and "-raw" or ""),"xml"  )
        local xhtmlfilebase         = addsuffix(usedname .. (useextra and "-tag" or ""),"xhtml")
        local htmlfilebase          = addsuffix(usedname .. (useextra and "-div" or ""),"html")
        local specificationfilebase = addsuffix(usedname .. (useextra and "-pub" or ""),"lua"  )

        local xmlfilename           = joinfile(basepath, xmlfilebase          )
        local xhtmlfilename         = joinfile(basepath, xhtmlfilebase        )
        local htmlfilename          = joinfile(basepath, htmlfilebase         )
        local specificationfilename = joinfile(basepath, specificationfilebase)
        --
        local defaultfilebase       = addsuffix(usedname .. "-defaults", "css")
        local imagefilebase         = addsuffix(usedname .. "-images",   "css")
        local fontfilebase          = addsuffix(usedname .. "-fonts",    "css")
        local stylefilebase         = addsuffix(usedname .. "-styles",   "css")
        local templatefilebase      = addsuffix(usedname .. "-templates","css")
        --
        local defaultfilename       = joinfile(stylepath,defaultfilebase )
        local imagefilename         = joinfile(stylepath,imagefilebase   )
        local stylefilename         = joinfile(stylepath,stylefilebase   )
        local fontfilename          = joinfile(stylepath,fontfilebase    )
        local templatefilename      = joinfile(stylepath,templatefilebase)

        local cssfile               = finetuning.cssfile

        -- we keep track of all used files

        local files = {
        }

        -- we always load the defaults and optionally extra css files; we also copy the example
        -- css file so that we always have the latest version

        local cssfiles = {
            defaultfilebase,
            imagefilebase,
            fontfilebase,
            stylefilebase,
            templatefilename,
        }

        local cssextra = cssfile and table.unique(settings_to_array(cssfile)) or { }

        -- at this point we're ready for the content; the collector also does some
        -- housekeeping and data collecting; at this point we still have an xml
        -- representation that uses verbose element names and carries information in
        -- attributes

        local result = allcontent(tree,false,true)

        -- ugly but so be it:
        local extradata = structures.tags.getextradata()

        if extradata then
            local t = { "" }
            t[#t+1] = "<extradata>"
            for name, action in sortedhash(extradata) do
                t[#t+1] = action()
            end
            t[#t+1] = "</extradata>"
            t[#t+1] = "</document>"
            -- we use a function because otherwise we can have a bad capture index
            result = gsub(result,"</document>",function()
                return concat(t,"\n")
            end)
        end

        -- done with ugly

        if onlyxml then

            os.remove(defaultfilename)
         -- os.remove(imagefilename)
         -- os.remove(fontfilename)
         -- os.remove(stylefilename)
         -- os.remove(templatefilename)

            for i=1,#cssextra do
                os.remove(joinfile(stylepath,basename(source)))
            end

         -- os.remove(xmlfilename)

            os.remove(imagefilename)
            os.remove(fontfilename)
            os.remove(stylefilename)
            os.remove(templatefilename)
            os.remove(xhtmlfilename)
            os.remove(specificationfilename)
            os.remove(htmlfilename)

            result = concat {
                wholepreamble(true,true),
                "<!-- This export file is used for filtering runtime only! -->\n",
                result,
            }

            report_export("saving xml data in %a",xmlfilename)
            io.savedata(xmlfilename,result)

            return

        end

        local examplefilename = resolvers.findfile("export-example.css")
        if examplefilename then
            local data = io.loaddata(examplefilename)
            if not data or data == "" then
                data = "/* missing css file */"
            elseif not usecssnamespace then
                data = gsub(data,cssnamespace,"")
            end
            io.savedata(defaultfilename,data)
        end

        if cssfile then
            for i=1,#cssextra do
                local source = addsuffix(cssextra[i],"css")
                local target = joinfile(stylepath,basename(source))
                cssfiles[#cssfiles+1] = source
                if not lfs.isfile(source) then
                    source = joinfile("../",source)
                end
                if lfs.isfile(source) then
                    report_export("copying %s",source)
                    file.copy(source,target)
                end
            end
        end


        local script = settings_to_hash(finetuning.option or "").mathjax and mathmlheadscript or nil

        local x_styles, h_styles = allusedstylesheets(cssfiles,files,"styles",script)

        local attach = backends.nodeinjections.attachfile

        if embedfile and attach then
            -- only for testing
            attach {
                data       = concat{ wholepreamble(true), result },
                name       = basename(xmlfilename),
                registered = "export",
                title      = "raw xml export",
                method     = v_hidden,
                mimetype   = "application/mathml+xml",
            }
        end

        result = concat {
            wholepreamble(true),
            x_styles, -- adds to files
            result,
        }

        cssfiles = table.unique(cssfiles)

        -- we're now ready for saving the result in the xml file

        if exportxml then

            report_export("saving xml data in %a",xmlfilename)
            io.savedata(xmlfilename,result)

        end

        report_export("saving css image definitions in %a",imagefilename)
        io.savedata(imagefilename,wrapups.allusedimages(usedname))

        report_export("saving css font definitions in %a",fontfilename)
        io.savedata(fontfilename,wrapups.allusedfonts(usedname))

        report_export("saving css style definitions in %a",stylefilename)
        io.savedata(stylefilename,wrapups.allusedstyles(usedname))

        report_export("saving css template in %a",templatefilename)
        io.savedata(templatefilename,allusedelements(usedname))

        -- additionally we save an xhtml file; for that we load the file as xml tree

        local xmltree = cleanxhtmltree(xml.convert(result))

        if exportxhtml then

            report_export("saving xhtml variant in %a",xhtmlfilename)

            -- for c in xml.collected(xmltree,"listitem[@href]") do
            --     local h = c.at.href
            --     if h then
            --         local l = xml.first(c,"listtag")
            --         if l then
            --             table.insert(l.dt,1,xml.convert("<A href='" .. c.at.href .. "'></A>").dt)
            --         end
            --     end
            -- end

            xml.save(xmltree,xhtmlfilename)

-- remap(specification,xmltree)

        end

        -- now we save a specification file that can be used for generating an epub file

        -- looking at identity is somewhat redundant as we also inherit from interaction
        -- at the tex end

        if exporthtml then

            local identity  = interactions.general.getidentity()
            local metadata  = structures.tags.getmetadata()

            local specification = {
                name       = usedname,
                identifier = os.uuid(),
                images     = wrapups.uniqueusedimages(),
                imagefile  = joinfile("styles",imagefilebase),
                imagepath  = "images",
                stylepath  = "styles",
                xmlfiles   = { xmlfilebase },
                xhtmlfiles = { xhtmlfilebase },
                htmlfiles  = { htmlfilebase },
                styles     = cssfiles,
                htmlroot   = htmlfilebase,
                language   = exportlanguage(texgetcount("mainlanguagenumber")),
                title      = validstring(finetuning.title) or validstring(identity.title),
                subtitle   = validstring(finetuning.subtitle) or validstring(identity.subtitle),
                author     = validstring(finetuning.author) or validstring(identity.author),
                firstpage  = validstring(finetuning.firstpage),
                lastpage   = validstring(finetuning.lastpage),
                metadata   = metadata,
            }

            report_export("saving specification in %a",specificationfilename,specificationfilename)

            xml.wipe(xmltree,"metadata") -- maybe optional

            io.savedata(specificationfilename,table.serialize(specification,true))

        -- the html export for epub is different in the sense that it uses div's instead of
        -- specific tags

            report_export("saving div based alternative in %a",htmlfilename)

            remap(specification,xmltree)

            -- believe it or not, but a <title/> can prevent viewing in browsers

            local title = specification.title

            if not title or title == "" then
                title = metadata.title
                if not title or title == "" then
                    title = usedname -- was: "no title"
                end
            end

            local language = exportlanguage(texgetcount("mainlanguagenumber"))

            local variables = {
                style    = h_styles,
                body     = xml.tostring(xml.first(xmltree,"/div")),
                preamble = wholepreamble(false),
                title    = title,
                language = exportlanguage(texgetcount("mainlanguagenumber")) or "en",
            }

            io.savedata(htmlfilename,replacetemplate(htmltemplate,variables,"xml"))

            -- finally we report how an epub file can be made (using the specification)

            report_export("")
            report_export('create epub with: mtxrun --script epub --make "%s" [--purge --rename --svgmath]',usedname)
            report_export("")

        end

        stoptiming(treehash)
    end

    local enableaction = nodes.tasks.enableaction

    statistics.feedback.register { name = "export", index = 1, category = "performance" }

    function structurestags.initializeexport()
        if not exporting then
            report_export("enabling export to xml")
            enableaction("shipouts","nodes.handlers.export")
         -- enableaction("shipouts","nodes.handlers.accessibility")
            enableaction("math",    "noads.handlers.tags")
            enableaction("everypar","nodes.handlers.checkparcounter")
            luatex.registerstopactions(structurestags.finishexport)
            exporting = true
            statistics.feedback.setstate("export", true)
        end
    end


    function structurestags.setupexport(t)
        merge(finetuning,t)
        keephyphens      = finetuning.hyphen == v_yes
        exportproperties = finetuning.properties
        if exportproperties == v_no then
            exportproperties = false
        end
    end

    statistics.register("xml exporting time", function()
        if exporting then
            return string.format("%s seconds, version %s", statistics.elapsedtime(treehash),exportversion)
        end
    end)

end

-- These are called at the tex end:

implement {
    name      = "setupexport",
    actions   = structurestags.setupexport,
    arguments = {
        {
            { "align" }, -- normally a number
            { "bodyfont", "dimen" },
            { "width", "dimen" },
            { "properties" },
            { "hyphen" },
            { "title" },
            { "subtitle" },
            { "author" },
            { "firstpage" },
            { "lastpage" },
            { "svgstyle" },
            { "cssfile" },
            { "file" },
            { "option" },
            { "export" },
        }
    }
}

implement {
    name      = "finishexport",
    actions   = structurestags.finishexport,
}

implement {
    name      = "initializeexport",
    actions   = structurestags.initializeexport,
}