xref: /netbsd-src/external/gpl3/gdb.old/dist/libctf/ctf-dedup.c (revision 6881a4007f077b54e5f51159c52b9b25f57deb0d)
17d62b00eSchristos /* CTF type deduplication.
2*6881a400Schristos    Copyright (C) 2019-2022 Free Software Foundation, Inc.
37d62b00eSchristos 
47d62b00eSchristos    This file is part of libctf.
57d62b00eSchristos 
67d62b00eSchristos    libctf is free software; you can redistribute it and/or modify it under
77d62b00eSchristos    the terms of the GNU General Public License as published by the Free
87d62b00eSchristos    Software Foundation; either version 3, or (at your option) any later
97d62b00eSchristos    version.
107d62b00eSchristos 
117d62b00eSchristos    This program is distributed in the hope that it will be useful, but
127d62b00eSchristos    WITHOUT ANY WARRANTY; without even the implied warranty of
137d62b00eSchristos    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
147d62b00eSchristos    See the GNU General Public License for more details.
157d62b00eSchristos 
167d62b00eSchristos    You should have received a copy of the GNU General Public License
177d62b00eSchristos    along with this program; see the file COPYING.  If not see
187d62b00eSchristos    <http://www.gnu.org/licenses/>.  */
197d62b00eSchristos 
207d62b00eSchristos #include <ctf-impl.h>
217d62b00eSchristos #include <string.h>
227d62b00eSchristos #include <errno.h>
237d62b00eSchristos #include <assert.h>
247d62b00eSchristos #include "hashtab.h"
257d62b00eSchristos 
267d62b00eSchristos /* (In the below, relevant functions are named in square brackets.)  */
277d62b00eSchristos 
287d62b00eSchristos /* Type deduplication is a three-phase process:
297d62b00eSchristos 
307d62b00eSchristos     [ctf_dedup, ctf_dedup_hash_type, ctf_dedup_rhash_type]
317d62b00eSchristos     1) come up with unambiguous hash values for all types: no two types may have
327d62b00eSchristos        the same hash value, and any given type should have only one hash value
337d62b00eSchristos        (for optimal deduplication).
347d62b00eSchristos 
357d62b00eSchristos     [ctf_dedup, ctf_dedup_detect_name_ambiguity,
367d62b00eSchristos      ctf_dedup_conflictify_unshared, ctf_dedup_mark_conflicting_hash]
377d62b00eSchristos     2) mark those distinct types with names that collide (and thus cannot be
387d62b00eSchristos        declared simultaneously in the same translation unit) as conflicting, and
397d62b00eSchristos        recursively mark all types that cite one of those types as conflicting as
407d62b00eSchristos        well.  Possibly mark all types cited in only one TU as conflicting, if
417d62b00eSchristos        the CTF_LINK_SHARE_DUPLICATED link mode is active.
427d62b00eSchristos 
437d62b00eSchristos     [ctf_dedup_emit, ctf_dedup_emit_struct_members, ctf_dedup_id_to_target]
447d62b00eSchristos     3) emit all the types, one hash value at a time.  Types not marked
457d62b00eSchristos        conflicting are emitted once, into the shared dictionary: types marked
467d62b00eSchristos        conflicting are emitted once per TU into a dictionary corresponding to
477d62b00eSchristos        each TU in which they appear.  Structs marked conflicting get at the very
487d62b00eSchristos        least a forward emitted into the shared dict so that other dicts can cite
497d62b00eSchristos        it if needed.
507d62b00eSchristos 
517d62b00eSchristos    [id_to_packed_id]
527d62b00eSchristos    This all works over an array of inputs (usually in the same order as the
537d62b00eSchristos    inputs on the link line).  We don't use the ctf_link_inputs hash directly
547d62b00eSchristos    because it is convenient to be able to address specific input types as a
557d62b00eSchristos    *global type ID* or 'GID', a pair of an array offset and a ctf_id_t.  Since
567d62b00eSchristos    both are already 32 bits or less or can easily be constrained to that range,
577d62b00eSchristos    we can pack them both into a single 64-bit hash word for easy lookups, which
58*6881a400Schristos    would be much more annoying to do with a ctf_dict_t * and a ctf_id_t.  (On
597d62b00eSchristos    32-bit platforms, we must do that anyway, since pointers, and thus hash keys
607d62b00eSchristos    and values, are only 32 bits wide).  We track which inputs are parents of
617d62b00eSchristos    which other inputs so that we can correctly recognize that types we have
627d62b00eSchristos    traversed in children may cite types in parents, and so that we can process
637d62b00eSchristos    the parents first.)
647d62b00eSchristos 
657d62b00eSchristos    Note that thanks to ld -r, the deduplicator can be fed its own output, so the
667d62b00eSchristos    inputs may themselves have child dicts.  Since we need to support this usage
677d62b00eSchristos    anyway, we can use it in one other place.  If the caller finds translation
687d62b00eSchristos    units to be too small a unit ambiguous types, links can be 'cu-mapped', where
697d62b00eSchristos    the caller provides a mapping of input TU names to output child dict names.
707d62b00eSchristos    This mapping can fuse many child TUs into one potential child dict, so that
717d62b00eSchristos    ambiguous types in any of those input TUs go into the same child dict.
727d62b00eSchristos    When a many:1 cu-mapping is detected, the ctf_dedup machinery is called
737d62b00eSchristos    repeatedly, once for every output name that has more than one input, to fuse
747d62b00eSchristos    all the input TUs associated with a given output dict into one, and once again
757d62b00eSchristos    as normal to deduplicate all those intermediate outputs (and any 1:1 inputs)
767d62b00eSchristos    together.  This has much higher memory usage than otherwise, because in the
777d62b00eSchristos    intermediate state, all the output TUs are in memory at once and cannot be
787d62b00eSchristos    lazily opened.  It also has implications for the emission code: if types
797d62b00eSchristos    appear ambiguously in multiple input TUs that are all mapped to the same
807d62b00eSchristos    child dict, we cannot put them in children in the cu-mapping link phase
817d62b00eSchristos    because this output is meant to *become* a child in the next link stage and
827d62b00eSchristos    parent/child relationships are only one level deep: so instead, we just hide
837d62b00eSchristos    all but one of the ambiguous types.
847d62b00eSchristos 
857d62b00eSchristos    There are a few other subtleties here that make this more complex than it
867d62b00eSchristos    seems.  Let's go over the steps above in more detail.
877d62b00eSchristos 
887d62b00eSchristos    1) HASHING.
897d62b00eSchristos 
907d62b00eSchristos    [ctf_dedup_hash_type, ctf_dedup_rhash_type]
917d62b00eSchristos    Hashing proceeds recursively, mixing in the properties of each input type
927d62b00eSchristos    (including its name, if any), and then adding the hash values of every type
937d62b00eSchristos    cited by that type.  The result is stashed in the cd_type_hashes so other
947d62b00eSchristos    phases can find the hash values of input types given their IDs, and so that
957d62b00eSchristos    if we encounter this type again while hashing we can just return its hash
967d62b00eSchristos    value: it is also stashed in the *output mapping*, a mapping from hash value
977d62b00eSchristos    to the set of GIDs corresponding to that type in all inputs.  We also keep
987d62b00eSchristos    track of the GID of the first appearance of the type in any input (in
997d62b00eSchristos    cd_output_first_gid), and the GID of structs, unions, and forwards that only
1007d62b00eSchristos    appear in one TU (in cd_struct_origin).  See below for where these things are
1017d62b00eSchristos    used.
1027d62b00eSchristos 
1037d62b00eSchristos    Everything in this phase is time-critical, because it is operating over
1047d62b00eSchristos    non-deduplicated types and so may have hundreds or thousands of times the
1057d62b00eSchristos    data volume to deal with than later phases.  Trace output is hidden behind
1067d62b00eSchristos    ENABLE_LIBCTF_HASH_DEBUGGING to prevent the sheer number of calls to
1077d62b00eSchristos    ctf_dprintf from slowing things down (tenfold slowdowns are observed purely
1087d62b00eSchristos    from the calls to ctf_dprintf(), even with debugging switched off), and keep
1097d62b00eSchristos    down the volume of output (hundreds of gigabytes of debug output are not
1107d62b00eSchristos    uncommon on larger links).
1117d62b00eSchristos 
1127d62b00eSchristos    We have to do *something* about potential cycles in the type graph.  We'd
1137d62b00eSchristos    like to avoid emitting forwards in the final output if possible, because
1147d62b00eSchristos    forwards aren't much use: they have no members.  We are mostly saved from
1157d62b00eSchristos    needing to worry about this at emission time by ctf_add_struct*()
1167d62b00eSchristos    automatically replacing newly-created forwards when the real struct/union
1177d62b00eSchristos    comes along.  So we only have to avoid getting stuck in cycles during the
1187d62b00eSchristos    hashing phase, while also not confusing types that cite members that are
1197d62b00eSchristos    structs with each other.  It is easiest to solve this problem by noting two
1207d62b00eSchristos    things:
1217d62b00eSchristos 
1227d62b00eSchristos     - all cycles in C depend on the presence of tagged structs/unions
1237d62b00eSchristos     - all tagged structs/unions have a unique name they can be disambiguated by
1247d62b00eSchristos 
1257d62b00eSchristos    [ctf_dedup_is_stub]
1267d62b00eSchristos    This means that we can break all cycles by ceasing to hash in cited types at
1277d62b00eSchristos    every tagged struct/union and instead hashing in a stub consisting of the
1287d62b00eSchristos    struct/union's *decorated name*, which is the name preceded by "s " or "u "
1297d62b00eSchristos    depending on the namespace (cached in cd_decorated_names).  Forwards are
1307d62b00eSchristos    decorated identically (so a forward to "struct foo" would be represented as
1317d62b00eSchristos    "s foo"): this means that a citation of a forward to a type and a citation of
1327d62b00eSchristos    a concrete definition of a type with the same name ends up getting the same
1337d62b00eSchristos    hash value.
1347d62b00eSchristos 
1357d62b00eSchristos    Of course, it is quite possible to have two TUs with structs with the same
1367d62b00eSchristos    name and different definitions, but that's OK because when we scan for types
1377d62b00eSchristos    with ambiguous names we will identify these and mark them conflicting.
1387d62b00eSchristos 
1397d62b00eSchristos    We populate one thing to help conflictedness marking.  No unconflicted type
1407d62b00eSchristos    may cite a conflicted one, but this means that conflictedness marking must
1417d62b00eSchristos    walk from types to the types that cite them, which is the opposite of the
1427d62b00eSchristos    usual order.  We can make this easier to do by constructing a *citers* graph
1437d62b00eSchristos    in cd_citers, which points from types to the types that cite them: because we
1447d62b00eSchristos    emit forwards corresponding to every conflicted struct/union, we don't need
1457d62b00eSchristos    to do this for citations of structs/unions by other types.  This is very
1467d62b00eSchristos    convenient for us, because that's the only type we don't traverse
1477d62b00eSchristos    recursively: so we can construct the citers graph at the same time as we
1487d62b00eSchristos    hash, rather than needing to add an extra pass.  (This graph is a dynhash of
1497d62b00eSchristos    *type hash values*, so it's small: in effect it is automatically
1507d62b00eSchristos    deduplicated.)
1517d62b00eSchristos 
1527d62b00eSchristos    2) COLLISIONAL MARKING.
1537d62b00eSchristos 
1547d62b00eSchristos    [ctf_dedup_detect_name_ambiguity, ctf_dedup_mark_conflicting_hash]
1557d62b00eSchristos    We identify types whose names collide during the hashing process, and count
1567d62b00eSchristos    the rough number of uses of each name (caching may throw it off a bit: this
1577d62b00eSchristos    doesn't need to be accurate).  We then mark the less-frequently-cited types
1587d62b00eSchristos    with each names conflicting: the most-frequently-cited one goes into the
1597d62b00eSchristos    shared type dictionary, while all others are duplicated into per-TU
1607d62b00eSchristos    dictionaries, named after the input TU, that have the shared dictionary as a
1617d62b00eSchristos    parent.  For structures and unions this is not quite good enough: we'd like
1627d62b00eSchristos    to have citations of forwards to ambiguously named structures and unions
1637d62b00eSchristos    *stay* as citations of forwards, so that the user can tell that the caller
1647d62b00eSchristos    didn't actually know which structure definition was meant: but if we put one
1657d62b00eSchristos    of those structures into the shared dictionary, it would supplant and replace
1667d62b00eSchristos    the forward, leaving no sign.  So structures and unions do not take part in
1677d62b00eSchristos    this popularity contest: if their names are ambiguous, they are just
1687d62b00eSchristos    duplicated, and only a forward appears in the shared dict.
1697d62b00eSchristos 
1707d62b00eSchristos    [ctf_dedup_propagate_conflictedness]
1717d62b00eSchristos    The process of marking types conflicted is itself recursive: we recursively
1727d62b00eSchristos    traverse the cd_citers graph populated in the hashing pass above and mark
1737d62b00eSchristos    everything that we encounter conflicted (without wasting time re-marking
1747d62b00eSchristos    anything that is already marked).  This naturally terminates just where we
1757d62b00eSchristos    want it to (at types that are cited by no other types, and at structures and
1767d62b00eSchristos    unions) and suffices to ensure that types that cite conflicted types are
1777d62b00eSchristos    always marked conflicted.
1787d62b00eSchristos 
1797d62b00eSchristos    [ctf_dedup_conflictify_unshared, ctf_dedup_multiple_input_dicts]
1807d62b00eSchristos    When linking in CTF_LINK_SHARE_DUPLICATED mode, we would like all types that
1817d62b00eSchristos    are used in only one TU to end up in a per-CU dict. The easiest way to do
1827d62b00eSchristos    that is to mark them conflicted.  ctf_dedup_conflictify_unshared does this,
1837d62b00eSchristos    traversing the output mapping and using ctf_dedup_multiple_input_dicts to
1847d62b00eSchristos    check the number of input dicts each distinct type hash value came from:
1857d62b00eSchristos    types that only came from one get marked conflicted.  One caveat here is that
1867d62b00eSchristos    we need to consider both structs and forwards to them: a struct that appears
1877d62b00eSchristos    in one TU and has a dozen citations to an opaque forward in other TUs should
1887d62b00eSchristos    *not* be considered to be used in only one TU, because users would find it
1897d62b00eSchristos    useful to be able to traverse into opaque structures of that sort: so we use
1907d62b00eSchristos    cd_struct_origin to check both structs/unions and the forwards corresponding
1917d62b00eSchristos    to them.
1927d62b00eSchristos 
1937d62b00eSchristos    3) EMISSION.
1947d62b00eSchristos 
1957d62b00eSchristos    [ctf_dedup_walk_output_mapping, ctf_dedup_rwalk_output_mapping,
1967d62b00eSchristos     ctf_dedup_rwalk_one_output_mapping]
1977d62b00eSchristos    Emission involves another walk of the entire output mapping, this time
1987d62b00eSchristos    traversing everything other than struct members, recursively.  Types are
1997d62b00eSchristos    emitted from leaves to trunk, emitting all types a type cites before emitting
2007d62b00eSchristos    the type itself.  We sort the output mapping before traversing it, for
2017d62b00eSchristos    reproducibility and also correctness: the input dicts may have parent/child
2027d62b00eSchristos    relationships, so we simply sort all types that first appear in parents
2037d62b00eSchristos    before all children, then sort types that first appear in dicts appearing
2047d62b00eSchristos    earlier on the linker command line before those that appear later, then sort
2057d62b00eSchristos    by input ctf_id_t.  (This is where we use cd_output_first_gid, collected
2067d62b00eSchristos    above.)
2077d62b00eSchristos 
2087d62b00eSchristos    The walking is done using a recursive traverser which arranges to not revisit
2097d62b00eSchristos    any type already visited and to call its callback once per input GID for
2107d62b00eSchristos    input GIDs corresponding to conflicted output types.  The traverser only
2117d62b00eSchristos    finds input types and calls a callback for them as many times as the output
2127d62b00eSchristos    needs to appear: it doesn't try to figure out anything about where the output
2137d62b00eSchristos    might go.  That's done by the callback based on whether the type is
2147d62b00eSchristos    marked conflicted or not.
2157d62b00eSchristos 
2167d62b00eSchristos    [ctf_dedup_emit_type, ctf_dedup_id_to_target, ctf_dedup_synthesize_forward]
2177d62b00eSchristos    ctf_dedup_emit_type is the (sole) callback for ctf_dedup_walk_output_mapping.
2187d62b00eSchristos    Conflicted types have all necessary dictionaries created, and then we emit
2197d62b00eSchristos    the type into each dictionary in turn, working over each input CTF type
2207d62b00eSchristos    corresponding to each hash value and using ctf_dedup_id_to_target to map each
2217d62b00eSchristos    input ctf_id_t into the corresponding type in the output (dealing with input
2227d62b00eSchristos    ctf_id_t's with parents in the process by simply chasing to the parent dict
2237d62b00eSchristos    if the type we're looking up is in there).  Emitting structures involves
2247d62b00eSchristos    simply noting that the members of this structure need emission later on:
2257d62b00eSchristos    because you cannot cite a single structure member from another type, we avoid
2267d62b00eSchristos    emitting the members at this stage to keep recursion depths down a bit.
2277d62b00eSchristos 
2287d62b00eSchristos    At this point, if we have by some mischance decided that two different types
2297d62b00eSchristos    with child types that hash to different values have in fact got the same hash
2307d62b00eSchristos    value themselves and *not* marked it conflicting, the type walk will walk
2317d62b00eSchristos    only *one* of them and in all likelihood we'll find that we are trying to
2327d62b00eSchristos    emit a type into some child dictionary that references a type that was never
2337d62b00eSchristos    emitted into that dictionary and assertion-fail.  This always indicates a bug
2347d62b00eSchristos    in the conflictedness marking machinery or the hashing code, or both.
2357d62b00eSchristos 
2367d62b00eSchristos    ctf_dedup_id_to_target calls ctf_dedup_synthesize_forward to do one extra
2377d62b00eSchristos    thing, alluded to above: if this is a conflicted tagged structure or union,
2387d62b00eSchristos    and the target is the shared dict (i.e., the type we're being asked to emit
2397d62b00eSchristos    is not itself conflicted so can't just point straight at the conflicted
2407d62b00eSchristos    type), we instead synthesise a forward with the same name, emit it into the
2417d62b00eSchristos    shared dict, record it in cd_output_emission_conflicted_forwards so that we
2427d62b00eSchristos    don't re-emit it, and return it.  This means that cycles that contain
2437d62b00eSchristos    conflicts do not cause the entire cycle to be replicated in every child: only
2447d62b00eSchristos    that piece of the cycle which takes you back as far as the closest tagged
2457d62b00eSchristos    struct/union needs to be replicated.  This trick means that no part of the
2467d62b00eSchristos    deduplicator needs a cycle detector: every recursive walk can stop at tagged
2477d62b00eSchristos    structures.
2487d62b00eSchristos 
2497d62b00eSchristos    [ctf_dedup_emit_struct_members]
2507d62b00eSchristos    The final stage of emission is to walk over all structures with members
2517d62b00eSchristos    that need emission and emit all of them. Every type has been emitted at
2527d62b00eSchristos    this stage, so emission cannot fail.
2537d62b00eSchristos 
2547d62b00eSchristos    [ctf_dedup_populate_type_mappings, ctf_dedup_populate_type_mapping]
2557d62b00eSchristos    Finally, we update the input -> output type ID mappings used by the ctf-link
2567d62b00eSchristos    machinery to update all the other sections.  This is surprisingly expensive
2577d62b00eSchristos    and may be replaced with a scheme which lets the ctf-link machinery extract
2587d62b00eSchristos    the needed info directly from the deduplicator.  */
2597d62b00eSchristos 
2607d62b00eSchristos /* Possible future optimizations are flagged with 'optimization opportunity'
2617d62b00eSchristos    below.  */
2627d62b00eSchristos 
2637d62b00eSchristos /* Global optimization opportunity: a GC pass, eliminating types with no direct
2647d62b00eSchristos    or indirect citations from the other sections in the dictionary.  */
2657d62b00eSchristos 
2667d62b00eSchristos /* Internal flag values for ctf_dedup_hash_type.  */
2677d62b00eSchristos 
2687d62b00eSchristos /* Child call: consider forwardable types equivalent to forwards or stubs below
2697d62b00eSchristos    this point.  */
2707d62b00eSchristos #define CTF_DEDUP_HASH_INTERNAL_CHILD         0x01
2717d62b00eSchristos 
2727d62b00eSchristos /* Transform references to single ctf_id_ts in passed-in inputs into a number
2737d62b00eSchristos    that will fit in a uint64_t.  Needs rethinking if CTF_MAX_TYPE is boosted.
2747d62b00eSchristos 
2757d62b00eSchristos    On 32-bit platforms, we pack things together differently: see the note
2767d62b00eSchristos    above.  */
2777d62b00eSchristos 
2787d62b00eSchristos #if UINTPTR_MAX < UINT64_MAX
2797d62b00eSchristos # define IDS_NEED_ALLOCATION 1
2807d62b00eSchristos # define CTF_DEDUP_GID(fp, input, type) id_to_packed_id (fp, input, type)
2817d62b00eSchristos # define CTF_DEDUP_GID_TO_INPUT(id) packed_id_to_input (id)
2827d62b00eSchristos # define CTF_DEDUP_GID_TO_TYPE(id) packed_id_to_type (id)
2837d62b00eSchristos #else
2847d62b00eSchristos # define CTF_DEDUP_GID(fp, input, type)	\
2857d62b00eSchristos   (void *) (((uint64_t) input) << 32 | (type))
2867d62b00eSchristos # define CTF_DEDUP_GID_TO_INPUT(id) ((int) (((uint64_t) id) >> 32))
2877d62b00eSchristos # define CTF_DEDUP_GID_TO_TYPE(id) (ctf_id_t) (((uint64_t) id) & ~(0xffffffff00000000ULL))
2887d62b00eSchristos #endif
2897d62b00eSchristos 
2907d62b00eSchristos #ifdef IDS_NEED_ALLOCATION
2917d62b00eSchristos 
2927d62b00eSchristos  /* This is the 32-bit path, which stores GIDs in a pool and returns a pointer
2937d62b00eSchristos     into the pool.  It is notably less efficient than the 64-bit direct storage
2947d62b00eSchristos     approach, but with a smaller key, this is all we can do.  */
2957d62b00eSchristos 
2967d62b00eSchristos static void *
297*6881a400Schristos id_to_packed_id (ctf_dict_t *fp, int input_num, ctf_id_t type)
2987d62b00eSchristos {
2997d62b00eSchristos   const void *lookup;
3007d62b00eSchristos   ctf_type_id_key_t *dynkey = NULL;
3017d62b00eSchristos   ctf_type_id_key_t key = { input_num, type };
3027d62b00eSchristos 
303*6881a400Schristos   if (!ctf_dynhash_lookup_kv (fp->ctf_dedup.cd_id_to_dict_t,
3047d62b00eSchristos 			      &key, &lookup, NULL))
3057d62b00eSchristos     {
3067d62b00eSchristos       if ((dynkey = malloc (sizeof (ctf_type_id_key_t))) == NULL)
3077d62b00eSchristos 	goto oom;
3087d62b00eSchristos       memcpy (dynkey, &key, sizeof (ctf_type_id_key_t));
3097d62b00eSchristos 
310*6881a400Schristos       if (ctf_dynhash_insert (fp->ctf_dedup.cd_id_to_dict_t, dynkey, NULL) < 0)
3117d62b00eSchristos 	goto oom;
3127d62b00eSchristos 
313*6881a400Schristos       ctf_dynhash_lookup_kv (fp->ctf_dedup.cd_id_to_dict_t,
3147d62b00eSchristos 			     dynkey, &lookup, NULL);
3157d62b00eSchristos     }
3167d62b00eSchristos   /* We use a raw assert() here because there isn't really a way to get any sort
3177d62b00eSchristos      of error back from this routine without vastly complicating things for the
3187d62b00eSchristos      much more common case of !IDS_NEED_ALLOCATION.  */
3197d62b00eSchristos   assert (lookup);
3207d62b00eSchristos   return (void *) lookup;
3217d62b00eSchristos 
3227d62b00eSchristos  oom:
3237d62b00eSchristos   free (dynkey);
3247d62b00eSchristos   ctf_set_errno (fp, ENOMEM);
3257d62b00eSchristos   return NULL;
3267d62b00eSchristos }
3277d62b00eSchristos 
3287d62b00eSchristos static int
3297d62b00eSchristos packed_id_to_input (const void *id)
3307d62b00eSchristos {
3317d62b00eSchristos   const ctf_type_id_key_t *key = (ctf_type_id_key_t *) id;
3327d62b00eSchristos 
3337d62b00eSchristos   return key->ctii_input_num;
3347d62b00eSchristos }
3357d62b00eSchristos 
3367d62b00eSchristos static ctf_id_t
3377d62b00eSchristos packed_id_to_type (const void *id)
3387d62b00eSchristos {
3397d62b00eSchristos   const ctf_type_id_key_t *key = (ctf_type_id_key_t *) id;
3407d62b00eSchristos 
3417d62b00eSchristos   return key->ctii_type;
3427d62b00eSchristos }
3437d62b00eSchristos #endif
3447d62b00eSchristos 
3457d62b00eSchristos /* Make an element in a dynhash-of-dynsets, or return it if already present.  */
3467d62b00eSchristos 
3477d62b00eSchristos static ctf_dynset_t *
3487d62b00eSchristos make_set_element (ctf_dynhash_t *set, const void *key)
3497d62b00eSchristos {
3507d62b00eSchristos   ctf_dynset_t *element;
3517d62b00eSchristos 
3527d62b00eSchristos   if ((element = ctf_dynhash_lookup (set, key)) == NULL)
3537d62b00eSchristos     {
3547d62b00eSchristos       if ((element = ctf_dynset_create (htab_hash_string,
355*6881a400Schristos 					htab_eq_string,
3567d62b00eSchristos 					NULL)) == NULL)
3577d62b00eSchristos 	return NULL;
3587d62b00eSchristos 
3597d62b00eSchristos       if (ctf_dynhash_insert (set, (void *) key, element) < 0)
3607d62b00eSchristos 	{
3617d62b00eSchristos 	  ctf_dynset_destroy (element);
3627d62b00eSchristos 	  return NULL;
3637d62b00eSchristos 	}
3647d62b00eSchristos     }
3657d62b00eSchristos 
3667d62b00eSchristos   return element;
3677d62b00eSchristos }
3687d62b00eSchristos 
3697d62b00eSchristos /* Initialize the dedup atoms table.  */
3707d62b00eSchristos int
371*6881a400Schristos ctf_dedup_atoms_init (ctf_dict_t *fp)
3727d62b00eSchristos {
3737d62b00eSchristos   if (fp->ctf_dedup_atoms)
3747d62b00eSchristos     return 0;
3757d62b00eSchristos 
3767d62b00eSchristos   if (!fp->ctf_dedup_atoms_alloc)
3777d62b00eSchristos     {
3787d62b00eSchristos       if ((fp->ctf_dedup_atoms_alloc
379*6881a400Schristos 	   = ctf_dynset_create (htab_hash_string, htab_eq_string,
3807d62b00eSchristos 				free)) == NULL)
3817d62b00eSchristos 	return ctf_set_errno (fp, ENOMEM);
3827d62b00eSchristos     }
3837d62b00eSchristos   fp->ctf_dedup_atoms = fp->ctf_dedup_atoms_alloc;
3847d62b00eSchristos   return 0;
3857d62b00eSchristos }
3867d62b00eSchristos 
3877d62b00eSchristos /* Intern things in the dedup atoms table.  */
3887d62b00eSchristos 
3897d62b00eSchristos static const char *
390*6881a400Schristos intern (ctf_dict_t *fp, char *atom)
3917d62b00eSchristos {
3927d62b00eSchristos   const void *foo;
3937d62b00eSchristos 
3947d62b00eSchristos   if (atom == NULL)
3957d62b00eSchristos     return NULL;
3967d62b00eSchristos 
3977d62b00eSchristos   if (!ctf_dynset_exists (fp->ctf_dedup_atoms, atom, &foo))
3987d62b00eSchristos     {
3997d62b00eSchristos       if (ctf_dynset_insert (fp->ctf_dedup_atoms, atom) < 0)
4007d62b00eSchristos 	{
4017d62b00eSchristos 	  ctf_set_errno (fp, ENOMEM);
4027d62b00eSchristos 	  return NULL;
4037d62b00eSchristos 	}
4047d62b00eSchristos       foo = atom;
4057d62b00eSchristos     }
4067d62b00eSchristos   else
4077d62b00eSchristos     free (atom);
4087d62b00eSchristos 
4097d62b00eSchristos   return (const char *) foo;
4107d62b00eSchristos }
4117d62b00eSchristos 
4127d62b00eSchristos /* Add an indication of the namespace to a type name in a way that is not valid
4137d62b00eSchristos    for C identifiers.  Used to maintain hashes of type names to other things
4147d62b00eSchristos    while allowing for the four C namespaces (normal, struct, union, enum).
4157d62b00eSchristos    Return a new dynamically-allocated string.  */
4167d62b00eSchristos static const char *
417*6881a400Schristos ctf_decorate_type_name (ctf_dict_t *fp, const char *name, int kind)
4187d62b00eSchristos {
4197d62b00eSchristos   ctf_dedup_t *d = &fp->ctf_dedup;
4207d62b00eSchristos   const char *ret;
4217d62b00eSchristos   const char *k;
4227d62b00eSchristos   char *p;
4237d62b00eSchristos   size_t i;
4247d62b00eSchristos 
4257d62b00eSchristos   switch (kind)
4267d62b00eSchristos     {
4277d62b00eSchristos     case CTF_K_STRUCT:
4287d62b00eSchristos       k = "s ";
4297d62b00eSchristos       i = 0;
4307d62b00eSchristos       break;
4317d62b00eSchristos     case CTF_K_UNION:
4327d62b00eSchristos       k = "u ";
4337d62b00eSchristos       i = 1;
4347d62b00eSchristos       break;
4357d62b00eSchristos     case CTF_K_ENUM:
4367d62b00eSchristos       k = "e ";
4377d62b00eSchristos       i = 2;
4387d62b00eSchristos       break;
4397d62b00eSchristos     default:
4407d62b00eSchristos       k = "";
4417d62b00eSchristos       i = 3;
4427d62b00eSchristos     }
4437d62b00eSchristos 
4447d62b00eSchristos   if ((ret = ctf_dynhash_lookup (d->cd_decorated_names[i], name)) == NULL)
4457d62b00eSchristos     {
4467d62b00eSchristos       char *str;
4477d62b00eSchristos 
4487d62b00eSchristos       if ((str = malloc (strlen (name) + strlen (k) + 1)) == NULL)
4497d62b00eSchristos 	goto oom;
4507d62b00eSchristos 
4517d62b00eSchristos       p = stpcpy (str, k);
4527d62b00eSchristos       strcpy (p, name);
4537d62b00eSchristos       ret = intern (fp, str);
4547d62b00eSchristos       if (!ret)
4557d62b00eSchristos 	goto oom;
4567d62b00eSchristos 
4577d62b00eSchristos       if (ctf_dynhash_cinsert (d->cd_decorated_names[i], name, ret) < 0)
4587d62b00eSchristos 	goto oom;
4597d62b00eSchristos     }
4607d62b00eSchristos 
4617d62b00eSchristos   return ret;
4627d62b00eSchristos 
4637d62b00eSchristos  oom:
4647d62b00eSchristos   ctf_set_errno (fp, ENOMEM);
4657d62b00eSchristos   return NULL;
4667d62b00eSchristos }
4677d62b00eSchristos 
4687d62b00eSchristos /* Hash a type, possibly debugging-dumping something about it as well.  */
4697d62b00eSchristos static inline void
4707d62b00eSchristos ctf_dedup_sha1_add (ctf_sha1_t *sha1, const void *buf, size_t len,
4717d62b00eSchristos 		    const char *description _libctf_unused_,
4727d62b00eSchristos 		    unsigned long depth _libctf_unused_)
4737d62b00eSchristos {
4747d62b00eSchristos   ctf_sha1_add (sha1, buf, len);
4757d62b00eSchristos 
4767d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
4777d62b00eSchristos   ctf_sha1_t tmp;
4787d62b00eSchristos   char tmp_hval[CTF_SHA1_SIZE];
4797d62b00eSchristos   tmp = *sha1;
4807d62b00eSchristos   ctf_sha1_fini (&tmp, tmp_hval);
4817d62b00eSchristos   ctf_dprintf ("%lu: after hash addition of %s: %s\n", depth, description,
4827d62b00eSchristos 	       tmp_hval);
4837d62b00eSchristos #endif
4847d62b00eSchristos }
4857d62b00eSchristos 
4867d62b00eSchristos static const char *
487*6881a400Schristos ctf_dedup_hash_type (ctf_dict_t *fp, ctf_dict_t *input,
488*6881a400Schristos 		     ctf_dict_t **inputs, uint32_t *parents,
4897d62b00eSchristos 		     int input_num, ctf_id_t type, int flags,
4907d62b00eSchristos 		     unsigned long depth,
491*6881a400Schristos 		     int (*populate_fun) (ctf_dict_t *fp,
492*6881a400Schristos 					  ctf_dict_t *input,
493*6881a400Schristos 					  ctf_dict_t **inputs,
4947d62b00eSchristos 					  int input_num,
4957d62b00eSchristos 					  ctf_id_t type,
4967d62b00eSchristos 					  void *id,
4977d62b00eSchristos 					  const char *decorated_name,
4987d62b00eSchristos 					  const char *hash));
4997d62b00eSchristos 
5007d62b00eSchristos /* Determine whether this type is being hashed as a stub (in which case it is
5017d62b00eSchristos    unsafe to cache it).  */
5027d62b00eSchristos static int
5037d62b00eSchristos ctf_dedup_is_stub (const char *name, int kind, int fwdkind, int flags)
5047d62b00eSchristos {
5057d62b00eSchristos   /* We can cache all types unless we are recursing to children and are hashing
5067d62b00eSchristos      in a tagged struct, union or forward, all of which are replaced with their
5077d62b00eSchristos      decorated name as a stub and will have different hash values when hashed at
5087d62b00eSchristos      the top level.  */
5097d62b00eSchristos 
5107d62b00eSchristos   return ((flags & CTF_DEDUP_HASH_INTERNAL_CHILD) && name
5117d62b00eSchristos 	  && (kind == CTF_K_STRUCT || kind == CTF_K_UNION
5127d62b00eSchristos 	      || (kind == CTF_K_FORWARD && (fwdkind == CTF_K_STRUCT
5137d62b00eSchristos 					    || fwdkind == CTF_K_UNION))));
5147d62b00eSchristos }
5157d62b00eSchristos 
5167d62b00eSchristos /* Populate struct_origin if need be (not already populated, or populated with
5177d62b00eSchristos    a different origin), in which case it must go to -1, "shared".)
5187d62b00eSchristos 
5197d62b00eSchristos    Only called for forwards or forwardable types with names, when the link mode
5207d62b00eSchristos    is CTF_LINK_SHARE_DUPLICATED.  */
5217d62b00eSchristos static int
522*6881a400Schristos ctf_dedup_record_origin (ctf_dict_t *fp, int input_num, const char *decorated,
5237d62b00eSchristos 			 void *id)
5247d62b00eSchristos {
5257d62b00eSchristos   ctf_dedup_t *d = &fp->ctf_dedup;
5267d62b00eSchristos   void *origin;
5277d62b00eSchristos   int populate_origin = 0;
5287d62b00eSchristos 
5297d62b00eSchristos   if (ctf_dynhash_lookup_kv (d->cd_struct_origin, decorated, NULL, &origin))
5307d62b00eSchristos     {
5317d62b00eSchristos       if (CTF_DEDUP_GID_TO_INPUT (origin) != input_num
5327d62b00eSchristos 	  && CTF_DEDUP_GID_TO_INPUT (origin) != -1)
5337d62b00eSchristos 	{
5347d62b00eSchristos 	  populate_origin = 1;
5357d62b00eSchristos 	  origin = CTF_DEDUP_GID (fp, -1, -1);
5367d62b00eSchristos 	}
5377d62b00eSchristos     }
5387d62b00eSchristos   else
5397d62b00eSchristos     {
5407d62b00eSchristos       populate_origin = 1;
5417d62b00eSchristos       origin = id;
5427d62b00eSchristos     }
5437d62b00eSchristos 
5447d62b00eSchristos   if (populate_origin)
5457d62b00eSchristos     if (ctf_dynhash_cinsert (d->cd_struct_origin, decorated, origin) < 0)
5467d62b00eSchristos       return ctf_set_errno (fp, errno);
5477d62b00eSchristos   return 0;
5487d62b00eSchristos }
5497d62b00eSchristos 
5507d62b00eSchristos /* Do the underlying hashing and recursion for ctf_dedup_hash_type (which it
5517d62b00eSchristos    calls, recursively).  */
5527d62b00eSchristos 
5537d62b00eSchristos static const char *
554*6881a400Schristos ctf_dedup_rhash_type (ctf_dict_t *fp, ctf_dict_t *input, ctf_dict_t **inputs,
5557d62b00eSchristos 		      uint32_t *parents, int input_num, ctf_id_t type,
5567d62b00eSchristos 		      void *type_id, const ctf_type_t *tp, const char *name,
5577d62b00eSchristos 		      const char *decorated, int kind, int flags,
5587d62b00eSchristos 		      unsigned long depth,
559*6881a400Schristos 		      int (*populate_fun) (ctf_dict_t *fp,
560*6881a400Schristos 					   ctf_dict_t *input,
561*6881a400Schristos 					   ctf_dict_t **inputs,
5627d62b00eSchristos 					   int input_num,
5637d62b00eSchristos 					   ctf_id_t type,
5647d62b00eSchristos 					   void *id,
5657d62b00eSchristos 					   const char *decorated_name,
5667d62b00eSchristos 					   const char *hash))
5677d62b00eSchristos {
5687d62b00eSchristos   ctf_dedup_t *d = &fp->ctf_dedup;
5697d62b00eSchristos   ctf_next_t *i = NULL;
5707d62b00eSchristos   ctf_sha1_t hash;
5717d62b00eSchristos   ctf_id_t child_type;
5727d62b00eSchristos   char hashbuf[CTF_SHA1_SIZE];
5737d62b00eSchristos   const char *hval = NULL;
5747d62b00eSchristos   const char *whaterr;
575*6881a400Schristos   int err = 0;
5767d62b00eSchristos 
5777d62b00eSchristos   const char *citer = NULL;
5787d62b00eSchristos   ctf_dynset_t *citers = NULL;
5797d62b00eSchristos 
5807d62b00eSchristos   /* Add a citer to the citers set.  */
5817d62b00eSchristos #define ADD_CITER(citers, hval)						\
5827d62b00eSchristos   do									\
5837d62b00eSchristos     {									\
5847d62b00eSchristos       whaterr = N_("error updating citers");				\
5857d62b00eSchristos       if (!citers)							\
5867d62b00eSchristos 	if ((citers = ctf_dynset_create (htab_hash_string,		\
587*6881a400Schristos 					 htab_eq_string,		\
5887d62b00eSchristos 					 NULL)) == NULL)		\
5897d62b00eSchristos 	  goto oom;							\
5907d62b00eSchristos       if (ctf_dynset_cinsert (citers, hval) < 0)			\
5917d62b00eSchristos 	goto oom;							\
592*6881a400Schristos     }									\
593*6881a400Schristos   while (0)
5947d62b00eSchristos 
5957d62b00eSchristos   /* If this is a named struct or union or a forward to one, and this is a child
5967d62b00eSchristos      traversal, treat this type as if it were a forward -- do not recurse to
5977d62b00eSchristos      children, ignore all content not already hashed in, and hash in the
5987d62b00eSchristos      decorated name of the type instead.  */
5997d62b00eSchristos 
6007d62b00eSchristos   if (ctf_dedup_is_stub (name, kind, tp->ctt_type, flags))
6017d62b00eSchristos     {
6027d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
6037d62b00eSchristos       ctf_dprintf ("Struct/union/forward citation: substituting forwarding "
6047d62b00eSchristos 		   "stub with decorated name %s\n", decorated);
6057d62b00eSchristos 
6067d62b00eSchristos #endif
6077d62b00eSchristos       ctf_sha1_init (&hash);
6087d62b00eSchristos       ctf_dedup_sha1_add (&hash, decorated, strlen (decorated) + 1,
6097d62b00eSchristos 			  "decorated struct/union/forward name", depth);
6107d62b00eSchristos       ctf_sha1_fini (&hash, hashbuf);
6117d62b00eSchristos 
6127d62b00eSchristos       if ((hval = intern (fp, strdup (hashbuf))) == NULL)
6137d62b00eSchristos 	{
6147d62b00eSchristos 	  ctf_err_warn (fp, 0, 0, _("%s (%i): out of memory during forwarding-"
6157d62b00eSchristos 				    "stub hashing for type with GID %p"),
6167d62b00eSchristos 			ctf_link_input_name (input), input_num, type_id);
6177d62b00eSchristos 	  return NULL;				/* errno is set for us.  */
6187d62b00eSchristos 	}
6197d62b00eSchristos 
6207d62b00eSchristos       /* In share-duplicated link mode, make sure the origin of this type is
6217d62b00eSchristos 	 recorded, even if this is a type in a parent dict which will not be
6227d62b00eSchristos 	 directly traversed.  */
6237d62b00eSchristos       if (d->cd_link_flags & CTF_LINK_SHARE_DUPLICATED
6247d62b00eSchristos 	  && ctf_dedup_record_origin (fp, input_num, decorated, type_id) < 0)
6257d62b00eSchristos 	return NULL;				/* errno is set for us.  */
6267d62b00eSchristos 
6277d62b00eSchristos       return hval;
6287d62b00eSchristos     }
6297d62b00eSchristos 
6307d62b00eSchristos   /* Now ensure that subsequent recursive calls (but *not* the top-level call)
6317d62b00eSchristos      get this treatment.  */
6327d62b00eSchristos   flags |= CTF_DEDUP_HASH_INTERNAL_CHILD;
6337d62b00eSchristos 
6347d62b00eSchristos   /* If this is a struct, union, or forward with a name, record the unique
6357d62b00eSchristos      originating input TU, if there is one.  */
6367d62b00eSchristos 
6377d62b00eSchristos   if (decorated && (ctf_forwardable_kind (kind) || kind != CTF_K_FORWARD))
6387d62b00eSchristos     if (d->cd_link_flags & CTF_LINK_SHARE_DUPLICATED
6397d62b00eSchristos 	&& ctf_dedup_record_origin (fp, input_num, decorated, type_id) < 0)
6407d62b00eSchristos       return NULL;				/* errno is set for us.  */
6417d62b00eSchristos 
642*6881a400Schristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
643*6881a400Schristos   ctf_dprintf ("%lu: hashing thing with ID %i/%lx (kind %i): %s.\n",
644*6881a400Schristos 	       depth, input_num, type, kind, name ? name : "");
645*6881a400Schristos #endif
646*6881a400Schristos 
647*6881a400Schristos   /* Some type kinds don't have names: the API provides no way to set the name,
648*6881a400Schristos      so the type the deduplicator outputs will be nameless even if the input
649*6881a400Schristos      somehow has a name, and the name should not be mixed into the hash.  */
650*6881a400Schristos 
651*6881a400Schristos   switch (kind)
652*6881a400Schristos     {
653*6881a400Schristos     case CTF_K_POINTER:
654*6881a400Schristos     case CTF_K_ARRAY:
655*6881a400Schristos     case CTF_K_FUNCTION:
656*6881a400Schristos     case CTF_K_VOLATILE:
657*6881a400Schristos     case CTF_K_CONST:
658*6881a400Schristos     case CTF_K_RESTRICT:
659*6881a400Schristos     case CTF_K_SLICE:
660*6881a400Schristos       name = NULL;
661*6881a400Schristos     }
662*6881a400Schristos 
6637d62b00eSchristos   /* Mix in invariant stuff, transforming the type kind if needed.  Note that
6647d62b00eSchristos      the vlen is *not* hashed in: the actual variable-length info is hashed in
6657d62b00eSchristos      instead, piecewise.  The vlen is not part of the type, only the
6667d62b00eSchristos      variable-length data is: identical types with distinct vlens are quite
6677d62b00eSchristos      possible.  Equally, we do not want to hash in the isroot flag: both the
6687d62b00eSchristos      compiler and the deduplicator set the nonroot flag to indicate clashes with
6697d62b00eSchristos      *other types in the same TU* with the same name: so two types can easily
6707d62b00eSchristos      have distinct nonroot flags, yet be exactly the same type.*/
6717d62b00eSchristos 
6727d62b00eSchristos   ctf_sha1_init (&hash);
6737d62b00eSchristos   if (name)
6747d62b00eSchristos     ctf_dedup_sha1_add (&hash, name, strlen (name) + 1, "name", depth);
6757d62b00eSchristos   ctf_dedup_sha1_add (&hash, &kind, sizeof (uint32_t), "kind", depth);
6767d62b00eSchristos 
6777d62b00eSchristos   /* Hash content of this type.  */
6787d62b00eSchristos   switch (kind)
6797d62b00eSchristos     {
6807d62b00eSchristos     case CTF_K_UNKNOWN:
6817d62b00eSchristos       /* No extra state.  */
6827d62b00eSchristos       break;
6837d62b00eSchristos     case CTF_K_FORWARD:
6847d62b00eSchristos 
6857d62b00eSchristos       /* Add the forwarded kind, stored in the ctt_type.  */
6867d62b00eSchristos       ctf_dedup_sha1_add (&hash, &tp->ctt_type, sizeof (tp->ctt_type),
6877d62b00eSchristos 			  "forwarded kind", depth);
6887d62b00eSchristos       break;
6897d62b00eSchristos     case CTF_K_INTEGER:
6907d62b00eSchristos     case CTF_K_FLOAT:
6917d62b00eSchristos       {
6927d62b00eSchristos 	ctf_encoding_t ep;
6937d62b00eSchristos 	memset (&ep, 0, sizeof (ctf_encoding_t));
6947d62b00eSchristos 
6957d62b00eSchristos 	ctf_dedup_sha1_add (&hash, &tp->ctt_size, sizeof (uint32_t), "size",
6967d62b00eSchristos 			    depth);
6977d62b00eSchristos 	if (ctf_type_encoding (input, type, &ep) < 0)
6987d62b00eSchristos 	  {
6997d62b00eSchristos 	    whaterr = N_("error getting encoding");
700*6881a400Schristos 	    goto input_err;
7017d62b00eSchristos 	  }
7027d62b00eSchristos 	ctf_dedup_sha1_add (&hash, &ep, sizeof (ctf_encoding_t), "encoding",
7037d62b00eSchristos 			    depth);
7047d62b00eSchristos 	break;
7057d62b00eSchristos       }
7067d62b00eSchristos       /* Types that reference other types.  */
7077d62b00eSchristos     case CTF_K_TYPEDEF:
7087d62b00eSchristos     case CTF_K_VOLATILE:
7097d62b00eSchristos     case CTF_K_CONST:
7107d62b00eSchristos     case CTF_K_RESTRICT:
7117d62b00eSchristos     case CTF_K_POINTER:
7127d62b00eSchristos       /* Hash the referenced type, if not already hashed, and mix it in.  */
7137d62b00eSchristos       child_type = ctf_type_reference (input, type);
7147d62b00eSchristos       if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents, input_num,
7157d62b00eSchristos 				       child_type, flags, depth,
7167d62b00eSchristos 				       populate_fun)) == NULL)
7177d62b00eSchristos 	{
7187d62b00eSchristos 	  whaterr = N_("error doing referenced type hashing");
7197d62b00eSchristos 	  goto err;
7207d62b00eSchristos 	}
7217d62b00eSchristos       ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "referenced type",
7227d62b00eSchristos 			  depth);
7237d62b00eSchristos       citer = hval;
7247d62b00eSchristos 
7257d62b00eSchristos       break;
7267d62b00eSchristos 
7277d62b00eSchristos       /* The slices of two types hash identically only if the type they overlay
7287d62b00eSchristos 	 also has the same encoding.  This is not ideal, but in practice will work
7297d62b00eSchristos 	 well enough.  We work directly rather than using the CTF API because
7307d62b00eSchristos 	 we do not want the slice's normal automatically-shine-through
7317d62b00eSchristos 	 semantics to kick in here.  */
7327d62b00eSchristos     case CTF_K_SLICE:
7337d62b00eSchristos       {
7347d62b00eSchristos 	const ctf_slice_t *slice;
7357d62b00eSchristos 	const ctf_dtdef_t *dtd;
7367d62b00eSchristos 	ssize_t size;
7377d62b00eSchristos 	ssize_t increment;
7387d62b00eSchristos 
7397d62b00eSchristos 	child_type = ctf_type_reference (input, type);
7407d62b00eSchristos 	ctf_get_ctt_size (input, tp, &size, &increment);
7417d62b00eSchristos 	ctf_dedup_sha1_add (&hash, &size, sizeof (ssize_t), "size", depth);
7427d62b00eSchristos 
7437d62b00eSchristos 	if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents, input_num,
7447d62b00eSchristos 					 child_type, flags, depth,
7457d62b00eSchristos 					 populate_fun)) == NULL)
7467d62b00eSchristos 	  {
7477d62b00eSchristos 	    whaterr = N_("error doing slice-referenced type hashing");
7487d62b00eSchristos 	    goto err;
7497d62b00eSchristos 	  }
7507d62b00eSchristos 	ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "sliced type",
7517d62b00eSchristos 			    depth);
7527d62b00eSchristos 	citer = hval;
7537d62b00eSchristos 
7547d62b00eSchristos 	if ((dtd = ctf_dynamic_type (input, type)) != NULL)
755*6881a400Schristos 	  slice = (ctf_slice_t *) dtd->dtd_vlen;
7567d62b00eSchristos 	else
7577d62b00eSchristos 	  slice = (ctf_slice_t *) ((uintptr_t) tp + increment);
7587d62b00eSchristos 
7597d62b00eSchristos 	ctf_dedup_sha1_add (&hash, &slice->cts_offset,
7607d62b00eSchristos 			    sizeof (slice->cts_offset), "slice offset", depth);
7617d62b00eSchristos 	ctf_dedup_sha1_add (&hash, &slice->cts_bits,
7627d62b00eSchristos 			    sizeof (slice->cts_bits), "slice bits", depth);
7637d62b00eSchristos 	break;
7647d62b00eSchristos       }
7657d62b00eSchristos 
7667d62b00eSchristos     case CTF_K_ARRAY:
7677d62b00eSchristos       {
7687d62b00eSchristos 	ctf_arinfo_t ar;
7697d62b00eSchristos 
7707d62b00eSchristos 	if (ctf_array_info (input, type, &ar) < 0)
7717d62b00eSchristos 	  {
7727d62b00eSchristos 	    whaterr = N_("error getting array info");
773*6881a400Schristos 	    goto input_err;
7747d62b00eSchristos 	  }
7757d62b00eSchristos 
7767d62b00eSchristos 	if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents, input_num,
7777d62b00eSchristos 					 ar.ctr_contents, flags, depth,
7787d62b00eSchristos 					 populate_fun)) == NULL)
7797d62b00eSchristos 	  {
7807d62b00eSchristos 	    whaterr = N_("error doing array contents type hashing");
7817d62b00eSchristos 	    goto err;
7827d62b00eSchristos 	  }
7837d62b00eSchristos 	ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "array contents",
7847d62b00eSchristos 			    depth);
7857d62b00eSchristos 	ADD_CITER (citers, hval);
7867d62b00eSchristos 
7877d62b00eSchristos 	if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents, input_num,
7887d62b00eSchristos 					 ar.ctr_index, flags, depth,
7897d62b00eSchristos 					 populate_fun)) == NULL)
7907d62b00eSchristos 	  {
7917d62b00eSchristos 	    whaterr = N_("error doing array index type hashing");
7927d62b00eSchristos 	    goto err;
7937d62b00eSchristos 	  }
7947d62b00eSchristos 	ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "array index",
7957d62b00eSchristos 			    depth);
7967d62b00eSchristos 	ctf_dedup_sha1_add (&hash, &ar.ctr_nelems, sizeof (ar.ctr_nelems),
7977d62b00eSchristos 			    "element count", depth);
7987d62b00eSchristos 	ADD_CITER (citers, hval);
7997d62b00eSchristos 
8007d62b00eSchristos 	break;
8017d62b00eSchristos       }
8027d62b00eSchristos     case CTF_K_FUNCTION:
8037d62b00eSchristos       {
8047d62b00eSchristos 	ctf_funcinfo_t fi;
8057d62b00eSchristos 	ctf_id_t *args;
8067d62b00eSchristos 	uint32_t j;
8077d62b00eSchristos 
8087d62b00eSchristos 	if (ctf_func_type_info (input, type, &fi) < 0)
8097d62b00eSchristos 	  {
8107d62b00eSchristos 	    whaterr = N_("error getting func type info");
811*6881a400Schristos 	    goto input_err;
8127d62b00eSchristos 	  }
8137d62b00eSchristos 
8147d62b00eSchristos 	if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents, input_num,
8157d62b00eSchristos 					 fi.ctc_return, flags, depth,
8167d62b00eSchristos 					 populate_fun)) == NULL)
8177d62b00eSchristos 	  {
8187d62b00eSchristos 	    whaterr = N_("error getting func return type");
8197d62b00eSchristos 	    goto err;
8207d62b00eSchristos 	  }
8217d62b00eSchristos 	ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "func return",
8227d62b00eSchristos 			    depth);
8237d62b00eSchristos 	ctf_dedup_sha1_add (&hash, &fi.ctc_argc, sizeof (fi.ctc_argc),
8247d62b00eSchristos 			    "func argc", depth);
8257d62b00eSchristos 	ctf_dedup_sha1_add (&hash, &fi.ctc_flags, sizeof (fi.ctc_flags),
8267d62b00eSchristos 			    "func flags", depth);
8277d62b00eSchristos 	ADD_CITER (citers, hval);
8287d62b00eSchristos 
8297d62b00eSchristos 	if ((args = calloc (fi.ctc_argc, sizeof (ctf_id_t))) == NULL)
8307d62b00eSchristos 	  {
831*6881a400Schristos 	    err = ENOMEM;
8327d62b00eSchristos 	    whaterr = N_("error doing memory allocation");
8337d62b00eSchristos 	    goto err;
8347d62b00eSchristos 	  }
8357d62b00eSchristos 
8367d62b00eSchristos 	if (ctf_func_type_args (input, type, fi.ctc_argc, args) < 0)
8377d62b00eSchristos 	  {
8387d62b00eSchristos 	    free (args);
8397d62b00eSchristos 	    whaterr = N_("error getting func arg type");
840*6881a400Schristos 	    goto input_err;
8417d62b00eSchristos 	  }
8427d62b00eSchristos 	for (j = 0; j < fi.ctc_argc; j++)
8437d62b00eSchristos 	  {
8447d62b00eSchristos 	    if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents,
8457d62b00eSchristos 					     input_num, args[j], flags, depth,
8467d62b00eSchristos 					     populate_fun)) == NULL)
8477d62b00eSchristos 	      {
8487d62b00eSchristos 		free (args);
8497d62b00eSchristos 		whaterr = N_("error doing func arg type hashing");
8507d62b00eSchristos 		goto err;
8517d62b00eSchristos 	      }
8527d62b00eSchristos 	    ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "func arg type",
8537d62b00eSchristos 				depth);
8547d62b00eSchristos 	    ADD_CITER (citers, hval);
8557d62b00eSchristos 	  }
8567d62b00eSchristos 	free (args);
8577d62b00eSchristos 	break;
8587d62b00eSchristos       }
8597d62b00eSchristos     case CTF_K_ENUM:
8607d62b00eSchristos       {
8617d62b00eSchristos 	int val;
8627d62b00eSchristos 	const char *ename;
8637d62b00eSchristos 
8647d62b00eSchristos 	ctf_dedup_sha1_add (&hash, &tp->ctt_size, sizeof (uint32_t),
8657d62b00eSchristos 			    "enum size", depth);
8667d62b00eSchristos 	while ((ename = ctf_enum_next (input, type, &i, &val)) != NULL)
8677d62b00eSchristos 	  {
8687d62b00eSchristos 	    ctf_dedup_sha1_add (&hash, ename, strlen (ename) + 1, "enumerator",
8697d62b00eSchristos 				depth);
8707d62b00eSchristos 	    ctf_dedup_sha1_add (&hash, &val, sizeof (val), "enumerand", depth);
8717d62b00eSchristos 	  }
8727d62b00eSchristos 	if (ctf_errno (input) != ECTF_NEXT_END)
8737d62b00eSchristos 	  {
8747d62b00eSchristos 	    whaterr = N_("error doing enum member iteration");
875*6881a400Schristos 	    goto input_err;
8767d62b00eSchristos 	  }
8777d62b00eSchristos 	break;
8787d62b00eSchristos       }
8797d62b00eSchristos     /* Top-level only.  */
8807d62b00eSchristos     case CTF_K_STRUCT:
8817d62b00eSchristos     case CTF_K_UNION:
8827d62b00eSchristos       {
8837d62b00eSchristos 	ssize_t offset;
8847d62b00eSchristos 	const char *mname;
8857d62b00eSchristos 	ctf_id_t membtype;
8867d62b00eSchristos 	ssize_t size;
8877d62b00eSchristos 
8887d62b00eSchristos 	ctf_get_ctt_size (input, tp, &size, NULL);
8897d62b00eSchristos 	ctf_dedup_sha1_add (&hash, &size, sizeof (ssize_t), "struct size",
8907d62b00eSchristos 			    depth);
8917d62b00eSchristos 
892*6881a400Schristos 	while ((offset = ctf_member_next (input, type, &i, &mname, &membtype,
893*6881a400Schristos 					  0)) >= 0)
8947d62b00eSchristos 	  {
8957d62b00eSchristos 	    if (mname == NULL)
8967d62b00eSchristos 	      mname = "";
8977d62b00eSchristos 	    ctf_dedup_sha1_add (&hash, mname, strlen (mname) + 1,
8987d62b00eSchristos 				"member name", depth);
8997d62b00eSchristos 
9007d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
9017d62b00eSchristos 	    ctf_dprintf ("%lu: Traversing to member %s\n", depth, mname);
9027d62b00eSchristos #endif
9037d62b00eSchristos 	    if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents,
9047d62b00eSchristos 					     input_num, membtype, flags, depth,
9057d62b00eSchristos 					     populate_fun)) == NULL)
9067d62b00eSchristos 	      {
9077d62b00eSchristos 		whaterr = N_("error doing struct/union member type hashing");
9087d62b00eSchristos 		goto iterr;
9097d62b00eSchristos 	      }
9107d62b00eSchristos 
9117d62b00eSchristos 	    ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "member hash",
9127d62b00eSchristos 				depth);
9137d62b00eSchristos 	    ctf_dedup_sha1_add (&hash, &offset, sizeof (offset), "member offset",
9147d62b00eSchristos 				depth);
9157d62b00eSchristos 	    ADD_CITER (citers, hval);
9167d62b00eSchristos 	  }
9177d62b00eSchristos 	if (ctf_errno (input) != ECTF_NEXT_END)
9187d62b00eSchristos 	  {
9197d62b00eSchristos 	    whaterr = N_("error doing struct/union member iteration");
920*6881a400Schristos 	    goto input_err;
9217d62b00eSchristos 	  }
9227d62b00eSchristos 	break;
9237d62b00eSchristos       }
9247d62b00eSchristos     default:
9257d62b00eSchristos       whaterr = N_("error: unknown type kind");
9267d62b00eSchristos       goto err;
9277d62b00eSchristos     }
9287d62b00eSchristos   ctf_sha1_fini (&hash, hashbuf);
9297d62b00eSchristos 
9307d62b00eSchristos   if ((hval = intern (fp, strdup (hashbuf))) == NULL)
9317d62b00eSchristos     {
9327d62b00eSchristos       whaterr = N_("cannot intern hash");
9337d62b00eSchristos       goto oom;
9347d62b00eSchristos     }
9357d62b00eSchristos 
9367d62b00eSchristos   /* Populate the citers for this type's subtypes, now the hash for the type
9377d62b00eSchristos      itself is known.  */
9387d62b00eSchristos   whaterr = N_("error tracking citers");
9397d62b00eSchristos 
9407d62b00eSchristos   if (citer)
9417d62b00eSchristos     {
9427d62b00eSchristos       ctf_dynset_t *citer_hashes;
9437d62b00eSchristos 
9447d62b00eSchristos       if ((citer_hashes = make_set_element (d->cd_citers, citer)) == NULL)
9457d62b00eSchristos 	goto oom;
9467d62b00eSchristos       if (ctf_dynset_cinsert (citer_hashes, hval) < 0)
9477d62b00eSchristos 	goto oom;
9487d62b00eSchristos     }
9497d62b00eSchristos   else if (citers)
9507d62b00eSchristos     {
9517d62b00eSchristos       const void *k;
9527d62b00eSchristos 
9537d62b00eSchristos       while ((err = ctf_dynset_cnext (citers, &i, &k)) == 0)
9547d62b00eSchristos 	{
9557d62b00eSchristos 	  ctf_dynset_t *citer_hashes;
9567d62b00eSchristos 	  citer = (const char *) k;
9577d62b00eSchristos 
9587d62b00eSchristos 	  if ((citer_hashes = make_set_element (d->cd_citers, citer)) == NULL)
9597d62b00eSchristos 	    goto oom;
9607d62b00eSchristos 
9617d62b00eSchristos 	  if (ctf_dynset_exists (citer_hashes, hval, NULL))
9627d62b00eSchristos 	    continue;
9637d62b00eSchristos 	  if (ctf_dynset_cinsert (citer_hashes, hval) < 0)
9647d62b00eSchristos 	    goto oom;
9657d62b00eSchristos 	}
9667d62b00eSchristos       if (err != ECTF_NEXT_END)
9677d62b00eSchristos 	goto err;
9687d62b00eSchristos       ctf_dynset_destroy (citers);
9697d62b00eSchristos     }
9707d62b00eSchristos 
9717d62b00eSchristos   return hval;
9727d62b00eSchristos 
9737d62b00eSchristos  iterr:
9747d62b00eSchristos   ctf_next_destroy (i);
975*6881a400Schristos  input_err:
976*6881a400Schristos   err = ctf_errno (input);
9777d62b00eSchristos  err:
9787d62b00eSchristos   ctf_sha1_fini (&hash, NULL);
979*6881a400Schristos   ctf_err_warn (fp, 0, err, _("%s (%i): %s: during type hashing for type %lx, "
9807d62b00eSchristos 			      "kind %i"), ctf_link_input_name (input),
9817d62b00eSchristos 		input_num, gettext (whaterr), type, kind);
9827d62b00eSchristos   return NULL;
9837d62b00eSchristos  oom:
9847d62b00eSchristos   ctf_set_errno (fp, errno);
9857d62b00eSchristos   ctf_err_warn (fp, 0, 0, _("%s (%i): %s: during type hashing for type %lx, "
9867d62b00eSchristos 			    "kind %i"), ctf_link_input_name (input),
9877d62b00eSchristos 		input_num, gettext (whaterr), type, kind);
9887d62b00eSchristos   return NULL;
9897d62b00eSchristos }
9907d62b00eSchristos 
9917d62b00eSchristos /* Hash a TYPE in the INPUT: FP is the eventual output, where the ctf_dedup
9927d62b00eSchristos    state is stored.  INPUT_NUM is the number of this input in the set of inputs.
9937d62b00eSchristos    Record its hash in FP's cd_type_hashes once it is known.  PARENTS is
9947d62b00eSchristos    described in the comment above ctf_dedup.
9957d62b00eSchristos 
9967d62b00eSchristos    (The flags argument currently accepts only the flag
9977d62b00eSchristos    CTF_DEDUP_HASH_INTERNAL_CHILD, an implementation detail used to prevent
9987d62b00eSchristos    struct/union hashing in recursive traversals below the TYPE.)
9997d62b00eSchristos 
10007d62b00eSchristos    We use the CTF API rather than direct access wherever possible, because types
10017d62b00eSchristos    that appear identical through the API should be considered identical, with
10027d62b00eSchristos    one exception: slices should only be considered identical to other slices,
10037d62b00eSchristos    not to the corresponding unsliced type.
10047d62b00eSchristos 
10057d62b00eSchristos    The POPULATE_FUN is a mandatory hook that populates other mappings with each
10067d62b00eSchristos    type we see (excepting types that are recursively hashed as stubs).  The
10077d62b00eSchristos    caller should not rely on the order of calls to this hook, though it will be
10087d62b00eSchristos    called at least once for every non-stub reference to every type.
10097d62b00eSchristos 
10107d62b00eSchristos    Returns a hash value (an atom), or NULL on error.  */
10117d62b00eSchristos 
10127d62b00eSchristos static const char *
1013*6881a400Schristos ctf_dedup_hash_type (ctf_dict_t *fp, ctf_dict_t *input,
1014*6881a400Schristos 		     ctf_dict_t **inputs, uint32_t *parents,
10157d62b00eSchristos 		     int input_num, ctf_id_t type, int flags,
10167d62b00eSchristos 		     unsigned long depth,
1017*6881a400Schristos 		     int (*populate_fun) (ctf_dict_t *fp,
1018*6881a400Schristos 					  ctf_dict_t *input,
1019*6881a400Schristos 					  ctf_dict_t **inputs,
10207d62b00eSchristos 					  int input_num,
10217d62b00eSchristos 					  ctf_id_t type,
10227d62b00eSchristos 					  void *id,
10237d62b00eSchristos 					  const char *decorated_name,
10247d62b00eSchristos 					  const char *hash))
10257d62b00eSchristos {
10267d62b00eSchristos   ctf_dedup_t *d = &fp->ctf_dedup;
10277d62b00eSchristos   const ctf_type_t *tp;
10287d62b00eSchristos   void *type_id;
10297d62b00eSchristos   const char *hval = NULL;
10307d62b00eSchristos   const char *name;
10317d62b00eSchristos   const char *whaterr;
10327d62b00eSchristos   const char *decorated = NULL;
10337d62b00eSchristos   uint32_t kind, fwdkind;
10347d62b00eSchristos 
10357d62b00eSchristos   depth++;
10367d62b00eSchristos 
10377d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
10387d62b00eSchristos   ctf_dprintf ("%lu: ctf_dedup_hash_type (%i, %lx, flags %x)\n", depth, input_num, type, flags);
10397d62b00eSchristos #endif
10407d62b00eSchristos 
10417d62b00eSchristos   /* The unimplemented type doesn't really exist, but must be noted in parent
10427d62b00eSchristos      hashes: so it gets a fixed, arbitrary hash.  */
10437d62b00eSchristos   if (type == 0)
10447d62b00eSchristos     return "00000000000000000000";
10457d62b00eSchristos 
10467d62b00eSchristos   /* Possible optimization: if the input type is in the parent type space, just
10477d62b00eSchristos      copy recursively-cited hashes from the parent's types into the output
10487d62b00eSchristos      mapping rather than rehashing them.  */
10497d62b00eSchristos 
10507d62b00eSchristos   type_id = CTF_DEDUP_GID (fp, input_num, type);
10517d62b00eSchristos 
10527d62b00eSchristos   if ((tp = ctf_lookup_by_id (&input, type)) == NULL)
10537d62b00eSchristos     {
10547d62b00eSchristos       ctf_set_errno (fp, ctf_errno (input));
10557d62b00eSchristos       ctf_err_warn (fp, 0, 0, _("%s (%i): lookup failure for type %lx: "
10567d62b00eSchristos 				"flags %x"), ctf_link_input_name (input),
10577d62b00eSchristos 		    input_num, type, flags);
10587d62b00eSchristos       return NULL;		/* errno is set for us.  */
10597d62b00eSchristos     }
10607d62b00eSchristos 
10617d62b00eSchristos   kind = LCTF_INFO_KIND (input, tp->ctt_info);
10627d62b00eSchristos   name = ctf_strraw (input, tp->ctt_name);
10637d62b00eSchristos 
10647d62b00eSchristos   if (tp->ctt_name == 0 || !name || name[0] == '\0')
10657d62b00eSchristos     name = NULL;
10667d62b00eSchristos 
10677d62b00eSchristos   /* Decorate the name appropriately for the namespace it appears in: forwards
10687d62b00eSchristos      appear in the namespace of their referent.  */
10697d62b00eSchristos 
10707d62b00eSchristos   fwdkind = kind;
10717d62b00eSchristos   if (name)
10727d62b00eSchristos     {
10737d62b00eSchristos       if (kind == CTF_K_FORWARD)
10747d62b00eSchristos 	fwdkind = tp->ctt_type;
10757d62b00eSchristos 
10767d62b00eSchristos       if ((decorated = ctf_decorate_type_name (fp, name, fwdkind)) == NULL)
10777d62b00eSchristos 	return NULL;				/* errno is set for us.  */
10787d62b00eSchristos     }
10797d62b00eSchristos 
10807d62b00eSchristos   /* If not hashing a stub, we can rely on various sorts of caches.
10817d62b00eSchristos 
10827d62b00eSchristos      Optimization opportunity: we may be able to avoid calling the populate_fun
10837d62b00eSchristos      sometimes here.  */
10847d62b00eSchristos 
10857d62b00eSchristos   if (!ctf_dedup_is_stub (name, kind, fwdkind, flags))
10867d62b00eSchristos     {
10877d62b00eSchristos       if ((hval = ctf_dynhash_lookup (d->cd_type_hashes, type_id)) != NULL)
10887d62b00eSchristos 	{
10897d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
10907d62b00eSchristos 	  ctf_dprintf ("%lu: Known hash for ID %i/%lx: %s\n", depth, input_num,
10917d62b00eSchristos 		       type,  hval);
10927d62b00eSchristos #endif
10937d62b00eSchristos 	  populate_fun (fp, input, inputs, input_num, type, type_id,
10947d62b00eSchristos 			decorated, hval);
10957d62b00eSchristos 
10967d62b00eSchristos 	  return hval;
10977d62b00eSchristos 	}
10987d62b00eSchristos     }
10997d62b00eSchristos 
11007d62b00eSchristos   /* We have never seen this type before, and must figure out its hash and the
11017d62b00eSchristos      hashes of the types it cites.
11027d62b00eSchristos 
11037d62b00eSchristos      Hash this type, and call ourselves recursively.  (The hashing part is
11047d62b00eSchristos      optional, and is disabled if overidden_hval is set.)  */
11057d62b00eSchristos 
11067d62b00eSchristos   if ((hval = ctf_dedup_rhash_type (fp, input, inputs, parents, input_num,
11077d62b00eSchristos 				    type, type_id, tp, name, decorated,
11087d62b00eSchristos 				    kind, flags, depth, populate_fun)) == NULL)
11097d62b00eSchristos     return NULL;				/* errno is set for us.  */
11107d62b00eSchristos 
11117d62b00eSchristos   /* The hash of this type is now known: record it unless caching is unsafe
11127d62b00eSchristos      because the hash value will change later.  This will be the final storage
11137d62b00eSchristos      of this type's hash, so we call the population function on it.  */
11147d62b00eSchristos 
11157d62b00eSchristos   if (!ctf_dedup_is_stub (name, kind, fwdkind, flags))
11167d62b00eSchristos     {
11177d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
11187d62b00eSchristos       ctf_dprintf ("Caching %lx, ID %p (%s), %s in final location\n", type,
11197d62b00eSchristos 		   type_id, name ? name : "", hval);
11207d62b00eSchristos #endif
11217d62b00eSchristos 
11227d62b00eSchristos       if (ctf_dynhash_cinsert (d->cd_type_hashes, type_id, hval) < 0)
11237d62b00eSchristos 	{
11247d62b00eSchristos 	  whaterr = N_("error hash caching");
11257d62b00eSchristos 	  goto oom;
11267d62b00eSchristos 	}
11277d62b00eSchristos 
11287d62b00eSchristos       if (populate_fun (fp, input, inputs, input_num, type, type_id,
11297d62b00eSchristos 			decorated, hval) < 0)
11307d62b00eSchristos 	{
11317d62b00eSchristos 	  whaterr = N_("error calling population function");
11327d62b00eSchristos 	  goto err;				/* errno is set for us. */
11337d62b00eSchristos 	}
11347d62b00eSchristos     }
11357d62b00eSchristos 
11367d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
11377d62b00eSchristos   ctf_dprintf ("%lu: Returning final hash for ID %i/%lx: %s\n", depth,
11387d62b00eSchristos 	       input_num, type, hval);
11397d62b00eSchristos #endif
11407d62b00eSchristos   return hval;
11417d62b00eSchristos 
11427d62b00eSchristos  oom:
11437d62b00eSchristos   ctf_set_errno (fp, errno);
11447d62b00eSchristos  err:
11457d62b00eSchristos   ctf_err_warn (fp, 0, 0, _("%s (%i): %s: during type hashing, "
11467d62b00eSchristos 			    "type %lx, kind %i"),
11477d62b00eSchristos 		ctf_link_input_name (input), input_num,
11487d62b00eSchristos 		gettext (whaterr), type, kind);
11497d62b00eSchristos   return NULL;
11507d62b00eSchristos }
11517d62b00eSchristos 
11527d62b00eSchristos /* Populate a number of useful mappings not directly used by the hashing
11537d62b00eSchristos    machinery: the output mapping, the cd_name_counts mapping from name -> hash
11547d62b00eSchristos    -> count of hashval deduplication state for a given hashed type, and the
11557d62b00eSchristos    cd_output_first_tu mapping.  */
11567d62b00eSchristos 
11577d62b00eSchristos static int
1158*6881a400Schristos ctf_dedup_populate_mappings (ctf_dict_t *fp, ctf_dict_t *input _libctf_unused_,
1159*6881a400Schristos 			     ctf_dict_t **inputs _libctf_unused_,
11607d62b00eSchristos 			     int input_num _libctf_unused_,
11617d62b00eSchristos 			     ctf_id_t type _libctf_unused_, void *id,
11627d62b00eSchristos 			     const char *decorated_name,
11637d62b00eSchristos 			     const char *hval)
11647d62b00eSchristos {
11657d62b00eSchristos   ctf_dedup_t *d = &fp->ctf_dedup;
11667d62b00eSchristos   ctf_dynset_t *type_ids;
11677d62b00eSchristos   ctf_dynhash_t *name_counts;
11687d62b00eSchristos   long int count;
11697d62b00eSchristos 
11707d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
11717d62b00eSchristos   ctf_dprintf ("Hash %s, %s, into output mapping for %i/%lx @ %s\n",
11727d62b00eSchristos 	       hval, decorated_name ? decorated_name : "(unnamed)",
11737d62b00eSchristos 	       input_num, type, ctf_link_input_name (input));
11747d62b00eSchristos 
11757d62b00eSchristos   const char *orig_hval;
11767d62b00eSchristos 
11777d62b00eSchristos   /* Make sure we never map a single GID to multiple hash values.  */
11787d62b00eSchristos 
11797d62b00eSchristos   if ((orig_hval = ctf_dynhash_lookup (d->cd_output_mapping_guard, id)) != NULL)
11807d62b00eSchristos     {
11817d62b00eSchristos       /* We can rely on pointer identity here, since all hashes are
11827d62b00eSchristos 	 interned.  */
11837d62b00eSchristos       if (!ctf_assert (fp, orig_hval == hval))
11847d62b00eSchristos 	return -1;
11857d62b00eSchristos     }
11867d62b00eSchristos   else
11877d62b00eSchristos     if (ctf_dynhash_cinsert (d->cd_output_mapping_guard, id, hval) < 0)
11887d62b00eSchristos       return ctf_set_errno (fp, errno);
11897d62b00eSchristos #endif
11907d62b00eSchristos 
11917d62b00eSchristos   /* Record the type in the output mapping: if this is the first time this type
11927d62b00eSchristos      has been seen, also record it in the cd_output_first_gid.  Because we
11937d62b00eSchristos      traverse types in TU order and we do not merge types after the hashing
11947d62b00eSchristos      phase, this will be the lowest TU this type ever appears in.  */
11957d62b00eSchristos 
11967d62b00eSchristos   if ((type_ids = ctf_dynhash_lookup (d->cd_output_mapping,
11977d62b00eSchristos 				      hval)) == NULL)
11987d62b00eSchristos     {
11997d62b00eSchristos       if (ctf_dynhash_cinsert (d->cd_output_first_gid, hval, id) < 0)
12007d62b00eSchristos 	return ctf_set_errno (fp, errno);
12017d62b00eSchristos 
12027d62b00eSchristos       if ((type_ids = ctf_dynset_create (htab_hash_pointer,
12037d62b00eSchristos 					 htab_eq_pointer,
12047d62b00eSchristos 					 NULL)) == NULL)
12057d62b00eSchristos 	return ctf_set_errno (fp, errno);
12067d62b00eSchristos       if (ctf_dynhash_insert (d->cd_output_mapping, (void *) hval,
12077d62b00eSchristos 			      type_ids) < 0)
12087d62b00eSchristos 	{
12097d62b00eSchristos 	  ctf_dynset_destroy (type_ids);
12107d62b00eSchristos 	  return ctf_set_errno (fp, errno);
12117d62b00eSchristos 	}
12127d62b00eSchristos     }
12137d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
12147d62b00eSchristos     {
12157d62b00eSchristos       /* Verify that all types with this hash are of the same kind, and that the
12167d62b00eSchristos 	 first TU a type was seen in never falls.  */
12177d62b00eSchristos 
12187d62b00eSchristos       int err;
12197d62b00eSchristos       const void *one_id;
12207d62b00eSchristos       ctf_next_t *i = NULL;
12217d62b00eSchristos       int orig_kind = ctf_type_kind_unsliced (input, type);
12227d62b00eSchristos       int orig_first_tu;
12237d62b00eSchristos 
12247d62b00eSchristos       orig_first_tu = CTF_DEDUP_GID_TO_INPUT
12257d62b00eSchristos 	(ctf_dynhash_lookup (d->cd_output_first_gid, hval));
12267d62b00eSchristos       if (!ctf_assert (fp, orig_first_tu <= CTF_DEDUP_GID_TO_INPUT (id)))
12277d62b00eSchristos 	return -1;
12287d62b00eSchristos 
12297d62b00eSchristos       while ((err = ctf_dynset_cnext (type_ids, &i, &one_id)) == 0)
12307d62b00eSchristos 	{
1231*6881a400Schristos 	  ctf_dict_t *foo = inputs[CTF_DEDUP_GID_TO_INPUT (one_id)];
12327d62b00eSchristos 	  ctf_id_t bar = CTF_DEDUP_GID_TO_TYPE (one_id);
12337d62b00eSchristos 	  if (ctf_type_kind_unsliced (foo, bar) != orig_kind)
12347d62b00eSchristos 	    {
12357d62b00eSchristos 	      ctf_err_warn (fp, 1, 0, "added wrong kind to output mapping "
12367d62b00eSchristos 			    "for hash %s named %s: %p/%lx from %s is "
12377d62b00eSchristos 			    "kind %i, but newly-added %p/%lx from %s is "
12387d62b00eSchristos 			    "kind %i", hval,
12397d62b00eSchristos 			    decorated_name ? decorated_name : "(unnamed)",
12407d62b00eSchristos 			    (void *) foo, bar,
12417d62b00eSchristos 			    ctf_link_input_name (foo),
12427d62b00eSchristos 			    ctf_type_kind_unsliced (foo, bar),
12437d62b00eSchristos 			    (void *) input, type,
12447d62b00eSchristos 			    ctf_link_input_name (input), orig_kind);
12457d62b00eSchristos 	      if (!ctf_assert (fp, ctf_type_kind_unsliced (foo, bar)
12467d62b00eSchristos 			       == orig_kind))
12477d62b00eSchristos 		return -1;
12487d62b00eSchristos 	    }
12497d62b00eSchristos 	}
12507d62b00eSchristos       if (err != ECTF_NEXT_END)
12517d62b00eSchristos 	return ctf_set_errno (fp, err);
12527d62b00eSchristos     }
12537d62b00eSchristos #endif
12547d62b00eSchristos 
12557d62b00eSchristos   /* This function will be repeatedly called for the same types many times:
12567d62b00eSchristos      don't waste time reinserting the same keys in that case.  */
12577d62b00eSchristos   if (!ctf_dynset_exists (type_ids, id, NULL)
12587d62b00eSchristos       && ctf_dynset_insert (type_ids, id) < 0)
12597d62b00eSchristos     return ctf_set_errno (fp, errno);
12607d62b00eSchristos 
12617d62b00eSchristos   /* The rest only needs to happen for types with names.  */
12627d62b00eSchristos   if (!decorated_name)
12637d62b00eSchristos     return 0;
12647d62b00eSchristos 
12657d62b00eSchristos   /* Count the number of occurrences of the hash value for this GID.  */
12667d62b00eSchristos 
12677d62b00eSchristos   hval = ctf_dynhash_lookup (d->cd_type_hashes, id);
12687d62b00eSchristos 
12697d62b00eSchristos   /* Mapping from name -> hash(hashval, count) not already present?  */
12707d62b00eSchristos   if ((name_counts = ctf_dynhash_lookup (d->cd_name_counts,
12717d62b00eSchristos 					 decorated_name)) == NULL)
12727d62b00eSchristos     {
12737d62b00eSchristos       if ((name_counts = ctf_dynhash_create (ctf_hash_string,
12747d62b00eSchristos 					     ctf_hash_eq_string,
12757d62b00eSchristos 					     NULL, NULL)) == NULL)
12767d62b00eSchristos 	  return ctf_set_errno (fp, errno);
12777d62b00eSchristos       if (ctf_dynhash_cinsert (d->cd_name_counts, decorated_name,
12787d62b00eSchristos 			       name_counts) < 0)
12797d62b00eSchristos 	{
12807d62b00eSchristos 	  ctf_dynhash_destroy (name_counts);
12817d62b00eSchristos 	  return ctf_set_errno (fp, errno);
12827d62b00eSchristos 	}
12837d62b00eSchristos     }
12847d62b00eSchristos 
12857d62b00eSchristos   /* This will, conveniently, return NULL (i.e. 0) for a new entry.  */
12867d62b00eSchristos   count = (long int) (uintptr_t) ctf_dynhash_lookup (name_counts, hval);
12877d62b00eSchristos 
12887d62b00eSchristos   if (ctf_dynhash_cinsert (name_counts, hval,
12897d62b00eSchristos 			   (const void *) (uintptr_t) (count + 1)) < 0)
12907d62b00eSchristos     return ctf_set_errno (fp, errno);
12917d62b00eSchristos 
12927d62b00eSchristos   return 0;
12937d62b00eSchristos }
12947d62b00eSchristos 
12957d62b00eSchristos /* Mark a single hash as corresponding to a conflicting type.  Mark all types
12967d62b00eSchristos    that cite it as conflicting as well, terminating the recursive walk only when
12977d62b00eSchristos    types that are already conflicted or types do not cite other types are seen.
12987d62b00eSchristos    (Tagged structures and unions do not appear in the cd_citers graph, so the
12997d62b00eSchristos    walk also terminates there, since any reference to a conflicting structure is
13007d62b00eSchristos    just going to reference an unconflicting forward instead: see
13017d62b00eSchristos    ctf_dedup_maybe_synthesize_forward.)  */
13027d62b00eSchristos 
13037d62b00eSchristos static int
1304*6881a400Schristos ctf_dedup_mark_conflicting_hash (ctf_dict_t *fp, const char *hval)
13057d62b00eSchristos {
13067d62b00eSchristos   ctf_dedup_t *d = &fp->ctf_dedup;
13077d62b00eSchristos   ctf_next_t *i = NULL;
13087d62b00eSchristos   int err;
13097d62b00eSchristos   const void *k;
13107d62b00eSchristos   ctf_dynset_t *citers;
13117d62b00eSchristos 
13127d62b00eSchristos   /* Mark conflicted if not already so marked.  */
13137d62b00eSchristos   if (ctf_dynset_exists (d->cd_conflicting_types, hval, NULL))
13147d62b00eSchristos     return 0;
13157d62b00eSchristos 
13167d62b00eSchristos   ctf_dprintf ("Marking %s as conflicted\n", hval);
13177d62b00eSchristos 
13187d62b00eSchristos   if (ctf_dynset_cinsert (d->cd_conflicting_types, hval) < 0)
13197d62b00eSchristos     {
13207d62b00eSchristos       ctf_dprintf ("Out of memory marking %s as conflicted\n", hval);
13217d62b00eSchristos       ctf_set_errno (fp, errno);
13227d62b00eSchristos       return -1;
13237d62b00eSchristos     }
13247d62b00eSchristos 
13257d62b00eSchristos   /* If any types cite this type, mark them conflicted too.  */
13267d62b00eSchristos   if ((citers = ctf_dynhash_lookup (d->cd_citers, hval)) == NULL)
13277d62b00eSchristos     return 0;
13287d62b00eSchristos 
13297d62b00eSchristos   while ((err = ctf_dynset_cnext (citers, &i, &k)) == 0)
13307d62b00eSchristos     {
13317d62b00eSchristos       const char *hv = (const char *) k;
13327d62b00eSchristos 
13337d62b00eSchristos       if (ctf_dynset_exists (d->cd_conflicting_types, hv, NULL))
13347d62b00eSchristos 	continue;
13357d62b00eSchristos 
13367d62b00eSchristos       if (ctf_dedup_mark_conflicting_hash (fp, hv) < 0)
13377d62b00eSchristos 	{
13387d62b00eSchristos 	  ctf_next_destroy (i);
13397d62b00eSchristos 	  return -1;				/* errno is set for us.  */
13407d62b00eSchristos 	}
13417d62b00eSchristos     }
13427d62b00eSchristos   if (err != ECTF_NEXT_END)
13437d62b00eSchristos     return ctf_set_errno (fp, err);
13447d62b00eSchristos 
13457d62b00eSchristos   return 0;
13467d62b00eSchristos }
13477d62b00eSchristos 
13487d62b00eSchristos /* Look up a type kind from the output mapping, given a type hash value.  */
13497d62b00eSchristos static int
1350*6881a400Schristos ctf_dedup_hash_kind (ctf_dict_t *fp, ctf_dict_t **inputs, const char *hash)
13517d62b00eSchristos {
13527d62b00eSchristos   ctf_dedup_t *d = &fp->ctf_dedup;
13537d62b00eSchristos   void *id;
13547d62b00eSchristos   ctf_dynset_t *type_ids;
13557d62b00eSchristos 
13567d62b00eSchristos   /* Precondition: the output mapping is populated.  */
13577d62b00eSchristos   if (!ctf_assert (fp, ctf_dynhash_elements (d->cd_output_mapping) > 0))
13587d62b00eSchristos     return -1;
13597d62b00eSchristos 
13607d62b00eSchristos   /* Look up some GID from the output hash for this type.  (They are all
13617d62b00eSchristos      identical, so we can pick any).  Don't assert if someone calls this
13627d62b00eSchristos      function wrongly, but do assert if the output mapping knows about the hash,
13637d62b00eSchristos      but has nothing associated with it.  */
13647d62b00eSchristos 
13657d62b00eSchristos   type_ids = ctf_dynhash_lookup (d->cd_output_mapping, hash);
13667d62b00eSchristos   if (!type_ids)
13677d62b00eSchristos     {
13687d62b00eSchristos       ctf_dprintf ("Looked up type kind by nonexistent hash %s.\n", hash);
13697d62b00eSchristos       return ctf_set_errno (fp, ECTF_INTERNAL);
13707d62b00eSchristos     }
13717d62b00eSchristos   id = ctf_dynset_lookup_any (type_ids);
13727d62b00eSchristos   if (!ctf_assert (fp, id))
13737d62b00eSchristos     return -1;
13747d62b00eSchristos 
13757d62b00eSchristos   return ctf_type_kind_unsliced (inputs[CTF_DEDUP_GID_TO_INPUT (id)],
13767d62b00eSchristos 				 CTF_DEDUP_GID_TO_TYPE (id));
13777d62b00eSchristos }
13787d62b00eSchristos 
13797d62b00eSchristos /* Used to keep a count of types: i.e. distinct type hash values.  */
13807d62b00eSchristos typedef struct ctf_dedup_type_counter
13817d62b00eSchristos {
1382*6881a400Schristos   ctf_dict_t *fp;
1383*6881a400Schristos   ctf_dict_t **inputs;
13847d62b00eSchristos   int num_non_forwards;
13857d62b00eSchristos } ctf_dedup_type_counter_t;
13867d62b00eSchristos 
13877d62b00eSchristos /* Add to the type counter for one name entry from the cd_name_counts.  */
13887d62b00eSchristos static int
13897d62b00eSchristos ctf_dedup_count_types (void *key_, void *value _libctf_unused_, void *arg_)
13907d62b00eSchristos {
13917d62b00eSchristos   const char *hval = (const char *) key_;
13927d62b00eSchristos   int kind;
13937d62b00eSchristos   ctf_dedup_type_counter_t *arg = (ctf_dedup_type_counter_t *) arg_;
13947d62b00eSchristos 
13957d62b00eSchristos   kind = ctf_dedup_hash_kind (arg->fp, arg->inputs, hval);
13967d62b00eSchristos 
13977d62b00eSchristos   /* We rely on ctf_dedup_hash_kind setting the fp to -ECTF_INTERNAL on error to
13987d62b00eSchristos      smuggle errors out of here.  */
13997d62b00eSchristos 
14007d62b00eSchristos   if (kind != CTF_K_FORWARD)
14017d62b00eSchristos     {
14027d62b00eSchristos       arg->num_non_forwards++;
14037d62b00eSchristos       ctf_dprintf ("Counting hash %s: kind %i: num_non_forwards is %i\n",
14047d62b00eSchristos 		   hval, kind, arg->num_non_forwards);
14057d62b00eSchristos     }
14067d62b00eSchristos 
14077d62b00eSchristos   /* We only need to know if there is more than one non-forward (an ambiguous
14087d62b00eSchristos      type): don't waste time iterating any more than needed to figure that
14097d62b00eSchristos      out.  */
14107d62b00eSchristos 
14117d62b00eSchristos   if (arg->num_non_forwards > 1)
14127d62b00eSchristos     return 1;
14137d62b00eSchristos 
14147d62b00eSchristos   return 0;
14157d62b00eSchristos }
14167d62b00eSchristos 
14177d62b00eSchristos /* Detect name ambiguity and mark ambiguous names as conflicting, other than the
14187d62b00eSchristos    most common.  */
14197d62b00eSchristos static int
1420*6881a400Schristos ctf_dedup_detect_name_ambiguity (ctf_dict_t *fp, ctf_dict_t **inputs)
14217d62b00eSchristos {
14227d62b00eSchristos   ctf_dedup_t *d = &fp->ctf_dedup;
14237d62b00eSchristos   ctf_next_t *i = NULL;
14247d62b00eSchristos   void *k;
14257d62b00eSchristos   void *v;
14267d62b00eSchristos   int err;
14277d62b00eSchristos   const char *whaterr;
14287d62b00eSchristos 
14297d62b00eSchristos   /* Go through cd_name_counts for all CTF namespaces in turn.  */
14307d62b00eSchristos 
14317d62b00eSchristos   while ((err = ctf_dynhash_next (d->cd_name_counts, &i, &k, &v)) == 0)
14327d62b00eSchristos     {
14337d62b00eSchristos       const char *decorated = (const char *) k;
14347d62b00eSchristos       ctf_dynhash_t *name_counts = (ctf_dynhash_t *) v;
14357d62b00eSchristos       ctf_next_t *j = NULL;
14367d62b00eSchristos 
14377d62b00eSchristos       /* If this is a forwardable kind or a forward (which we can tell without
14387d62b00eSchristos 	 consulting the type because its decorated name has a space as its
14397d62b00eSchristos 	 second character: see ctf_decorate_type_name), we are only interested
14407d62b00eSchristos 	 in whether this name has many hashes associated with it: any such name
14417d62b00eSchristos 	 is necessarily ambiguous, and types with that name are conflicting.
14427d62b00eSchristos 	 Once we know whether this is true, we can skip to the next name: so use
14437d62b00eSchristos 	 ctf_dynhash_iter_find for efficiency.  */
14447d62b00eSchristos 
14457d62b00eSchristos       if (decorated[0] != '\0' && decorated[1] == ' ')
14467d62b00eSchristos 	{
14477d62b00eSchristos 	  ctf_dedup_type_counter_t counters = { fp, inputs, 0 };
14487d62b00eSchristos 	  ctf_dynhash_t *counts = (ctf_dynhash_t *) v;
14497d62b00eSchristos 
14507d62b00eSchristos 	  ctf_dynhash_iter_find (counts, ctf_dedup_count_types, &counters);
14517d62b00eSchristos 
14527d62b00eSchristos 	  /* Check for assertion failure and pass it up.  */
14537d62b00eSchristos 	  if (ctf_errno (fp) == ECTF_INTERNAL)
14547d62b00eSchristos 	    goto assert_err;
14557d62b00eSchristos 
14567d62b00eSchristos 	  if (counters.num_non_forwards > 1)
14577d62b00eSchristos 	    {
14587d62b00eSchristos 	      const void *hval_;
14597d62b00eSchristos 
14607d62b00eSchristos 	      while ((err = ctf_dynhash_cnext (counts, &j, &hval_, NULL)) == 0)
14617d62b00eSchristos 		{
14627d62b00eSchristos 		  const char *hval = (const char *) hval_;
14637d62b00eSchristos 		  ctf_dynset_t *type_ids;
14647d62b00eSchristos 		  void *id;
14657d62b00eSchristos 		  int kind;
14667d62b00eSchristos 
14677d62b00eSchristos 		  /* Dig through the types in this hash to find the non-forwards
14687d62b00eSchristos 		     and mark them ambiguous.  */
14697d62b00eSchristos 
14707d62b00eSchristos 		  type_ids = ctf_dynhash_lookup (d->cd_output_mapping, hval);
14717d62b00eSchristos 
14727d62b00eSchristos 		  /* Nonexistent? Must be a forward with no referent.  */
14737d62b00eSchristos 		  if (!type_ids)
14747d62b00eSchristos 		    continue;
14757d62b00eSchristos 
14767d62b00eSchristos 		  id = ctf_dynset_lookup_any (type_ids);
14777d62b00eSchristos 
14787d62b00eSchristos 		  kind = ctf_type_kind (inputs[CTF_DEDUP_GID_TO_INPUT (id)],
14797d62b00eSchristos 					CTF_DEDUP_GID_TO_TYPE (id));
14807d62b00eSchristos 
14817d62b00eSchristos 		  if (kind != CTF_K_FORWARD)
14827d62b00eSchristos 		    {
14837d62b00eSchristos 		      ctf_dprintf ("Marking %p, with hash %s, conflicting: one "
14847d62b00eSchristos 				   "of many non-forward GIDs for %s\n", id,
14857d62b00eSchristos 				   hval, (char *) k);
14867d62b00eSchristos 		      ctf_dedup_mark_conflicting_hash (fp, hval);
14877d62b00eSchristos 		    }
14887d62b00eSchristos 		}
14897d62b00eSchristos 	      if (err != ECTF_NEXT_END)
14907d62b00eSchristos 		{
14917d62b00eSchristos 		  whaterr = N_("error marking conflicting structs/unions");
14927d62b00eSchristos 		  goto iterr;
14937d62b00eSchristos 		}
14947d62b00eSchristos 	    }
14957d62b00eSchristos 	}
14967d62b00eSchristos       else
14977d62b00eSchristos 	{
14987d62b00eSchristos 	  /* This is an ordinary type.  Find the most common type with this
14997d62b00eSchristos 	     name, and mark it unconflicting: all others are conflicting.  (We
15007d62b00eSchristos 	     cannot do this sort of popularity contest with forwardable types
15017d62b00eSchristos 	     because any forwards to that type would be immediately unified with
15027d62b00eSchristos 	     the most-popular type on insertion, and we want conflicting structs
15037d62b00eSchristos 	     et al to have all forwards left intact, so the user is notified
15047d62b00eSchristos 	     that this type is conflicting.  TODO: improve this in future by
1505*6881a400Schristos 	     setting such forwards non-root-visible.)
1506*6881a400Schristos 
1507*6881a400Schristos 	     If multiple distinct types are "most common", pick the one that
1508*6881a400Schristos 	     appears first on the link line, and within that, the one with the
1509*6881a400Schristos 	     lowest type ID.  (See sort_output_mapping.)  */
15107d62b00eSchristos 
15117d62b00eSchristos 	  const void *key;
15127d62b00eSchristos 	  const void *count;
15137d62b00eSchristos 	  const char *hval;
15147d62b00eSchristos 	  long max_hcount = -1;
1515*6881a400Schristos 	  void *max_gid = NULL;
15167d62b00eSchristos 	  const char *max_hval = NULL;
15177d62b00eSchristos 
15187d62b00eSchristos 	  if (ctf_dynhash_elements (name_counts) <= 1)
15197d62b00eSchristos 	    continue;
15207d62b00eSchristos 
15217d62b00eSchristos 	  /* First find the most common.  */
15227d62b00eSchristos 	  while ((err = ctf_dynhash_cnext (name_counts, &j, &key, &count)) == 0)
15237d62b00eSchristos 	    {
15247d62b00eSchristos 	      hval = (const char *) key;
1525*6881a400Schristos 
15267d62b00eSchristos 	      if ((long int) (uintptr_t) count > max_hcount)
15277d62b00eSchristos 		{
15287d62b00eSchristos 		  max_hcount = (long int) (uintptr_t) count;
15297d62b00eSchristos 		  max_hval = hval;
1530*6881a400Schristos 		  max_gid = ctf_dynhash_lookup (d->cd_output_first_gid, hval);
1531*6881a400Schristos 		}
1532*6881a400Schristos 	      else if ((long int) (uintptr_t) count == max_hcount)
1533*6881a400Schristos 		{
1534*6881a400Schristos 		  void *gid = ctf_dynhash_lookup (d->cd_output_first_gid, hval);
1535*6881a400Schristos 
1536*6881a400Schristos 		  if (CTF_DEDUP_GID_TO_INPUT(gid) < CTF_DEDUP_GID_TO_INPUT(max_gid)
1537*6881a400Schristos 		      || (CTF_DEDUP_GID_TO_INPUT(gid) == CTF_DEDUP_GID_TO_INPUT(max_gid)
1538*6881a400Schristos 			  && CTF_DEDUP_GID_TO_TYPE(gid) < CTF_DEDUP_GID_TO_TYPE(max_gid)))
1539*6881a400Schristos 		    {
1540*6881a400Schristos 		      max_hval = hval;
1541*6881a400Schristos 		      max_gid = ctf_dynhash_lookup (d->cd_output_first_gid, hval);
1542*6881a400Schristos 		    }
15437d62b00eSchristos 		}
15447d62b00eSchristos 	    }
15457d62b00eSchristos 	  if (err != ECTF_NEXT_END)
15467d62b00eSchristos 	    {
15477d62b00eSchristos 	      whaterr = N_("error finding commonest conflicting type");
15487d62b00eSchristos 	      goto iterr;
15497d62b00eSchristos 	    }
15507d62b00eSchristos 
15517d62b00eSchristos 	  /* Mark all the others as conflicting.   */
15527d62b00eSchristos 	  while ((err = ctf_dynhash_cnext (name_counts, &j, &key, NULL)) == 0)
15537d62b00eSchristos 	    {
15547d62b00eSchristos 	      hval = (const char *) key;
15557d62b00eSchristos 	      if (strcmp (max_hval, hval) == 0)
15567d62b00eSchristos 		continue;
15577d62b00eSchristos 
15587d62b00eSchristos 	      ctf_dprintf ("Marking %s, an uncommon hash for %s, conflicting\n",
15597d62b00eSchristos 			   hval, (const char *) k);
15607d62b00eSchristos 	      if (ctf_dedup_mark_conflicting_hash (fp, hval) < 0)
15617d62b00eSchristos 		{
15627d62b00eSchristos 		  whaterr = N_("error marking hashes as conflicting");
15637d62b00eSchristos 		  goto err;
15647d62b00eSchristos 		}
15657d62b00eSchristos 	    }
15667d62b00eSchristos 	  if (err != ECTF_NEXT_END)
15677d62b00eSchristos 	    {
15687d62b00eSchristos 	      whaterr = N_("marking uncommon conflicting types");
15697d62b00eSchristos 	      goto iterr;
15707d62b00eSchristos 	    }
15717d62b00eSchristos 	}
15727d62b00eSchristos     }
15737d62b00eSchristos   if (err != ECTF_NEXT_END)
15747d62b00eSchristos     {
15757d62b00eSchristos       whaterr = N_("scanning for ambiguous names");
15767d62b00eSchristos       goto iterr;
15777d62b00eSchristos     }
15787d62b00eSchristos 
15797d62b00eSchristos   return 0;
15807d62b00eSchristos 
15817d62b00eSchristos  err:
15827d62b00eSchristos   ctf_next_destroy (i);
15837d62b00eSchristos   ctf_err_warn (fp, 0, 0, "%s", gettext (whaterr));
15847d62b00eSchristos   return -1;					/* errno is set for us.  */
15857d62b00eSchristos 
15867d62b00eSchristos  iterr:
15877d62b00eSchristos   ctf_err_warn (fp, 0, err, _("iteration failed: %s"), gettext (whaterr));
15887d62b00eSchristos   return ctf_set_errno (fp, err);
15897d62b00eSchristos 
15907d62b00eSchristos  assert_err:
15917d62b00eSchristos   ctf_next_destroy (i);
15927d62b00eSchristos   return -1; 					/* errno is set for us.  */
15937d62b00eSchristos }
15947d62b00eSchristos 
15957d62b00eSchristos /* Initialize the deduplication machinery.  */
15967d62b00eSchristos 
15977d62b00eSchristos static int
1598*6881a400Schristos ctf_dedup_init (ctf_dict_t *fp)
15997d62b00eSchristos {
16007d62b00eSchristos   ctf_dedup_t *d = &fp->ctf_dedup;
16017d62b00eSchristos   size_t i;
16027d62b00eSchristos 
16037d62b00eSchristos   if (ctf_dedup_atoms_init (fp) < 0)
16047d62b00eSchristos       goto oom;
16057d62b00eSchristos 
16067d62b00eSchristos #if IDS_NEED_ALLOCATION
1607*6881a400Schristos   if ((d->cd_id_to_dict_t = ctf_dynhash_create (ctf_hash_type_id_key,
16087d62b00eSchristos 						ctf_hash_eq_type_id_key,
16097d62b00eSchristos 						free, NULL)) == NULL)
16107d62b00eSchristos     goto oom;
16117d62b00eSchristos #endif
16127d62b00eSchristos 
16137d62b00eSchristos   for (i = 0; i < 4; i++)
16147d62b00eSchristos     {
16157d62b00eSchristos       if ((d->cd_decorated_names[i] = ctf_dynhash_create (ctf_hash_string,
16167d62b00eSchristos 							  ctf_hash_eq_string,
16177d62b00eSchristos 							  NULL, NULL)) == NULL)
16187d62b00eSchristos 	goto oom;
16197d62b00eSchristos     }
16207d62b00eSchristos 
16217d62b00eSchristos   if ((d->cd_name_counts
16227d62b00eSchristos        = ctf_dynhash_create (ctf_hash_string,
16237d62b00eSchristos 			     ctf_hash_eq_string, NULL,
16247d62b00eSchristos 			     (ctf_hash_free_fun) ctf_dynhash_destroy)) == NULL)
16257d62b00eSchristos     goto oom;
16267d62b00eSchristos 
16277d62b00eSchristos   if ((d->cd_type_hashes
16287d62b00eSchristos        = ctf_dynhash_create (ctf_hash_integer,
16297d62b00eSchristos 			     ctf_hash_eq_integer,
16307d62b00eSchristos 			     NULL, NULL)) == NULL)
16317d62b00eSchristos     goto oom;
16327d62b00eSchristos 
16337d62b00eSchristos   if ((d->cd_struct_origin
16347d62b00eSchristos        = ctf_dynhash_create (ctf_hash_string,
16357d62b00eSchristos 			     ctf_hash_eq_string,
16367d62b00eSchristos 			     NULL, NULL)) == NULL)
16377d62b00eSchristos     goto oom;
16387d62b00eSchristos 
16397d62b00eSchristos   if ((d->cd_citers
16407d62b00eSchristos        = ctf_dynhash_create (ctf_hash_string,
16417d62b00eSchristos 			     ctf_hash_eq_string, NULL,
16427d62b00eSchristos 			     (ctf_hash_free_fun) ctf_dynset_destroy)) == NULL)
16437d62b00eSchristos     goto oom;
16447d62b00eSchristos 
16457d62b00eSchristos   if ((d->cd_output_mapping
16467d62b00eSchristos        = ctf_dynhash_create (ctf_hash_string,
16477d62b00eSchristos 			     ctf_hash_eq_string, NULL,
16487d62b00eSchristos 			     (ctf_hash_free_fun) ctf_dynset_destroy)) == NULL)
16497d62b00eSchristos     goto oom;
16507d62b00eSchristos 
16517d62b00eSchristos   if ((d->cd_output_first_gid
16527d62b00eSchristos        = ctf_dynhash_create (ctf_hash_string,
16537d62b00eSchristos 			     ctf_hash_eq_string,
16547d62b00eSchristos 			     NULL, NULL)) == NULL)
16557d62b00eSchristos     goto oom;
16567d62b00eSchristos 
16577d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
16587d62b00eSchristos   if ((d->cd_output_mapping_guard
16597d62b00eSchristos        = ctf_dynhash_create (ctf_hash_integer,
16607d62b00eSchristos 			     ctf_hash_eq_integer, NULL, NULL)) == NULL)
16617d62b00eSchristos     goto oom;
16627d62b00eSchristos #endif
16637d62b00eSchristos 
1664*6881a400Schristos   if ((d->cd_input_nums
1665*6881a400Schristos        = ctf_dynhash_create (ctf_hash_integer,
1666*6881a400Schristos 			     ctf_hash_eq_integer,
1667*6881a400Schristos 			     NULL, NULL)) == NULL)
1668*6881a400Schristos     goto oom;
1669*6881a400Schristos 
16707d62b00eSchristos   if ((d->cd_emission_struct_members
16717d62b00eSchristos        = ctf_dynhash_create (ctf_hash_integer,
16727d62b00eSchristos 			     ctf_hash_eq_integer,
16737d62b00eSchristos 			     NULL, NULL)) == NULL)
16747d62b00eSchristos     goto oom;
16757d62b00eSchristos 
16767d62b00eSchristos   if ((d->cd_conflicting_types
16777d62b00eSchristos        = ctf_dynset_create (htab_hash_string,
1678*6881a400Schristos 			    htab_eq_string, NULL)) == NULL)
16797d62b00eSchristos     goto oom;
16807d62b00eSchristos 
16817d62b00eSchristos   return 0;
16827d62b00eSchristos 
16837d62b00eSchristos  oom:
16847d62b00eSchristos   ctf_err_warn (fp, 0, ENOMEM, _("ctf_dedup_init: cannot initialize: "
16857d62b00eSchristos 				 "out of memory"));
16867d62b00eSchristos   return ctf_set_errno (fp, ENOMEM);
16877d62b00eSchristos }
16887d62b00eSchristos 
1689*6881a400Schristos /* No ctf_dedup calls are allowed after this call other than starting a new
1690*6881a400Schristos    deduplication via ctf_dedup (not even ctf_dedup_type_mapping lookups).  */
16917d62b00eSchristos void
1692*6881a400Schristos ctf_dedup_fini (ctf_dict_t *fp, ctf_dict_t **outputs, uint32_t noutputs)
16937d62b00eSchristos {
16947d62b00eSchristos   ctf_dedup_t *d = &fp->ctf_dedup;
16957d62b00eSchristos   size_t i;
16967d62b00eSchristos 
16977d62b00eSchristos   /* ctf_dedup_atoms is kept across links.  */
16987d62b00eSchristos #if IDS_NEED_ALLOCATION
1699*6881a400Schristos   ctf_dynhash_destroy (d->cd_id_to_dict_t);
17007d62b00eSchristos #endif
17017d62b00eSchristos   for (i = 0; i < 4; i++)
17027d62b00eSchristos     ctf_dynhash_destroy (d->cd_decorated_names[i]);
17037d62b00eSchristos   ctf_dynhash_destroy (d->cd_name_counts);
17047d62b00eSchristos   ctf_dynhash_destroy (d->cd_type_hashes);
17057d62b00eSchristos   ctf_dynhash_destroy (d->cd_struct_origin);
17067d62b00eSchristos   ctf_dynhash_destroy (d->cd_citers);
17077d62b00eSchristos   ctf_dynhash_destroy (d->cd_output_mapping);
17087d62b00eSchristos   ctf_dynhash_destroy (d->cd_output_first_gid);
17097d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
17107d62b00eSchristos   ctf_dynhash_destroy (d->cd_output_mapping_guard);
17117d62b00eSchristos #endif
1712*6881a400Schristos   ctf_dynhash_destroy (d->cd_input_nums);
17137d62b00eSchristos   ctf_dynhash_destroy (d->cd_emission_struct_members);
17147d62b00eSchristos   ctf_dynset_destroy (d->cd_conflicting_types);
17157d62b00eSchristos 
17167d62b00eSchristos   /* Free the per-output state.  */
17177d62b00eSchristos   if (outputs)
17187d62b00eSchristos     {
17197d62b00eSchristos       for (i = 0; i < noutputs; i++)
17207d62b00eSchristos 	{
17217d62b00eSchristos 	  ctf_dedup_t *od = &outputs[i]->ctf_dedup;
17227d62b00eSchristos 	  ctf_dynhash_destroy (od->cd_output_emission_hashes);
17237d62b00eSchristos 	  ctf_dynhash_destroy (od->cd_output_emission_conflicted_forwards);
1724*6881a400Schristos 	  ctf_dict_close (od->cd_output);
17257d62b00eSchristos 	}
17267d62b00eSchristos     }
17277d62b00eSchristos   memset (d, 0, sizeof (ctf_dedup_t));
17287d62b00eSchristos }
17297d62b00eSchristos 
17307d62b00eSchristos /* Return 1 if this type is cited by multiple input dictionaries.  */
17317d62b00eSchristos 
17327d62b00eSchristos static int
1733*6881a400Schristos ctf_dedup_multiple_input_dicts (ctf_dict_t *output, ctf_dict_t **inputs,
17347d62b00eSchristos 				const char *hval)
17357d62b00eSchristos {
17367d62b00eSchristos   ctf_dedup_t *d = &output->ctf_dedup;
17377d62b00eSchristos   ctf_dynset_t *type_ids;
17387d62b00eSchristos   ctf_next_t *i = NULL;
17397d62b00eSchristos   void *id;
1740*6881a400Schristos   ctf_dict_t *found = NULL, *relative_found = NULL;
17417d62b00eSchristos   const char *type_id;
1742*6881a400Schristos   ctf_dict_t *input_fp;
17437d62b00eSchristos   ctf_id_t input_id;
17447d62b00eSchristos   const char *name;
17457d62b00eSchristos   const char *decorated;
17467d62b00eSchristos   int fwdkind;
17477d62b00eSchristos   int multiple = 0;
17487d62b00eSchristos   int err;
17497d62b00eSchristos 
17507d62b00eSchristos   type_ids = ctf_dynhash_lookup (d->cd_output_mapping, hval);
17517d62b00eSchristos   if (!ctf_assert (output, type_ids))
17527d62b00eSchristos     return -1;
17537d62b00eSchristos 
17547d62b00eSchristos   /* Scan across the IDs until we find proof that two disjoint dictionaries
17557d62b00eSchristos      are referenced.  Exit as soon as possible.  Optimization opportunity, but
17567d62b00eSchristos      possibly not worth it, given that this is only executed in
17577d62b00eSchristos      CTF_LINK_SHARE_DUPLICATED mode.  */
17587d62b00eSchristos 
17597d62b00eSchristos   while ((err = ctf_dynset_next (type_ids, &i, &id)) == 0)
17607d62b00eSchristos     {
1761*6881a400Schristos       ctf_dict_t *fp = inputs[CTF_DEDUP_GID_TO_INPUT (id)];
17627d62b00eSchristos 
17637d62b00eSchristos       if (fp == found || fp == relative_found)
17647d62b00eSchristos 	continue;
17657d62b00eSchristos 
17667d62b00eSchristos       if (!found)
17677d62b00eSchristos 	{
17687d62b00eSchristos 	  found = fp;
17697d62b00eSchristos 	  continue;
17707d62b00eSchristos 	}
17717d62b00eSchristos 
17727d62b00eSchristos       if (!relative_found
17737d62b00eSchristos 	  && (fp->ctf_parent == found || found->ctf_parent == fp))
17747d62b00eSchristos 	{
17757d62b00eSchristos 	  relative_found = fp;
17767d62b00eSchristos 	  continue;
17777d62b00eSchristos 	}
17787d62b00eSchristos 
17797d62b00eSchristos       multiple = 1;
17807d62b00eSchristos       ctf_next_destroy (i);
17817d62b00eSchristos       break;
17827d62b00eSchristos     }
17837d62b00eSchristos   if ((err != ECTF_NEXT_END) && (err != 0))
17847d62b00eSchristos     {
17857d62b00eSchristos       ctf_err_warn (output, 0, err, _("iteration error "
17867d62b00eSchristos 				      "propagating conflictedness"));
17877d62b00eSchristos       return ctf_set_errno (output, err);
17887d62b00eSchristos     }
17897d62b00eSchristos 
17907d62b00eSchristos   if (multiple)
17917d62b00eSchristos     return multiple;
17927d62b00eSchristos 
17937d62b00eSchristos   /* This type itself does not appear in multiple input dicts: how about another
17947d62b00eSchristos      related type with the same name (e.g. a forward if this is a struct,
17957d62b00eSchristos      etc).  */
17967d62b00eSchristos 
17977d62b00eSchristos   type_id = ctf_dynset_lookup_any (type_ids);
17987d62b00eSchristos   if (!ctf_assert (output, type_id))
17997d62b00eSchristos     return -1;
18007d62b00eSchristos 
18017d62b00eSchristos   input_fp = inputs[CTF_DEDUP_GID_TO_INPUT (type_id)];
18027d62b00eSchristos   input_id = CTF_DEDUP_GID_TO_TYPE (type_id);
18037d62b00eSchristos   fwdkind = ctf_type_kind_forwarded (input_fp, input_id);
18047d62b00eSchristos   name = ctf_type_name_raw (input_fp, input_id);
18057d62b00eSchristos 
18067d62b00eSchristos   if ((fwdkind == CTF_K_STRUCT || fwdkind == CTF_K_UNION)
1807*6881a400Schristos       && name[0] != '\0')
18087d62b00eSchristos     {
18097d62b00eSchristos       const void *origin;
18107d62b00eSchristos 
18117d62b00eSchristos       if ((decorated = ctf_decorate_type_name (output, name,
18127d62b00eSchristos 					       fwdkind)) == NULL)
18137d62b00eSchristos 	return -1;				/* errno is set for us.  */
18147d62b00eSchristos 
18157d62b00eSchristos       origin = ctf_dynhash_lookup (d->cd_struct_origin, decorated);
18167d62b00eSchristos       if ((origin != NULL) && (CTF_DEDUP_GID_TO_INPUT (origin) < 0))
18177d62b00eSchristos 	multiple = 1;
18187d62b00eSchristos     }
18197d62b00eSchristos 
18207d62b00eSchristos   return multiple;
18217d62b00eSchristos }
18227d62b00eSchristos 
18237d62b00eSchristos /* Demote unconflicting types which reference only one input, or which reference
18247d62b00eSchristos    two inputs where one input is the parent of the other, into conflicting
18257d62b00eSchristos    types.  Only used if the link mode is CTF_LINK_SHARE_DUPLICATED.  */
18267d62b00eSchristos 
18277d62b00eSchristos static int
1828*6881a400Schristos ctf_dedup_conflictify_unshared (ctf_dict_t *output, ctf_dict_t **inputs)
18297d62b00eSchristos {
18307d62b00eSchristos   ctf_dedup_t *d = &output->ctf_dedup;
18317d62b00eSchristos   ctf_next_t *i = NULL;
18327d62b00eSchristos   int err;
18337d62b00eSchristos   const void *k;
18347d62b00eSchristos   ctf_dynset_t *to_mark = NULL;
18357d62b00eSchristos 
1836*6881a400Schristos   if ((to_mark = ctf_dynset_create (htab_hash_string, htab_eq_string,
18377d62b00eSchristos 				    NULL)) == NULL)
18387d62b00eSchristos     goto err_no;
18397d62b00eSchristos 
18407d62b00eSchristos   while ((err = ctf_dynhash_cnext (d->cd_output_mapping, &i, &k, NULL)) == 0)
18417d62b00eSchristos     {
18427d62b00eSchristos       const char *hval = (const char *) k;
18437d62b00eSchristos       int conflicting;
18447d62b00eSchristos 
18457d62b00eSchristos       /* Types referenced by only one dict, with no type appearing under that
18467d62b00eSchristos 	 name elsewhere, are marked conflicting.  */
18477d62b00eSchristos 
18487d62b00eSchristos       conflicting = !ctf_dedup_multiple_input_dicts (output, inputs, hval);
18497d62b00eSchristos 
18507d62b00eSchristos       if (conflicting < 0)
18517d62b00eSchristos 	goto err;				/* errno is set for us.  */
18527d62b00eSchristos 
18537d62b00eSchristos       if (conflicting)
18547d62b00eSchristos 	if (ctf_dynset_cinsert (to_mark, hval) < 0)
18557d62b00eSchristos 	  goto err;
18567d62b00eSchristos     }
18577d62b00eSchristos   if (err != ECTF_NEXT_END)
18587d62b00eSchristos     goto iterr;
18597d62b00eSchristos 
18607d62b00eSchristos   while ((err = ctf_dynset_cnext (to_mark, &i, &k)) == 0)
18617d62b00eSchristos     {
18627d62b00eSchristos       const char *hval = (const char *) k;
18637d62b00eSchristos 
18647d62b00eSchristos       if (ctf_dedup_mark_conflicting_hash (output, hval) < 0)
18657d62b00eSchristos 	goto err;
18667d62b00eSchristos     }
18677d62b00eSchristos   if (err != ECTF_NEXT_END)
18687d62b00eSchristos     goto iterr;
18697d62b00eSchristos 
18707d62b00eSchristos   ctf_dynset_destroy (to_mark);
18717d62b00eSchristos 
18727d62b00eSchristos   return 0;
18737d62b00eSchristos 
18747d62b00eSchristos  err_no:
18757d62b00eSchristos   ctf_set_errno (output, errno);
18767d62b00eSchristos  err:
18777d62b00eSchristos   err = ctf_errno (output);
18787d62b00eSchristos   ctf_next_destroy (i);
18797d62b00eSchristos  iterr:
18807d62b00eSchristos   ctf_dynset_destroy (to_mark);
18817d62b00eSchristos   ctf_err_warn (output, 0, err, _("conflictifying unshared types"));
18827d62b00eSchristos   return ctf_set_errno (output, err);
18837d62b00eSchristos }
18847d62b00eSchristos 
18857d62b00eSchristos /* The core deduplicator.  Populate cd_output_mapping in the output ctf_dedup
18867d62b00eSchristos    with a mapping of all types that belong in this dictionary and where they
18877d62b00eSchristos    come from, and cd_conflicting_types with an indication of whether each type
18887d62b00eSchristos    is conflicted or not.  OUTPUT is the top-level output: INPUTS is the array of
18897d62b00eSchristos    input dicts; NINPUTS is the size of that array; PARENTS is an NINPUTS-element
18907d62b00eSchristos    array with each element corresponding to a input which is a child dict set to
18917d62b00eSchristos    the number in the INPUTS array of that input's parent.
18927d62b00eSchristos 
18937d62b00eSchristos    If CU_MAPPED is set, this is a first pass for a link with a non-empty CU
18947d62b00eSchristos    mapping: only one output will result.
18957d62b00eSchristos 
18967d62b00eSchristos    Only deduplicates: does not emit the types into the output.  Call
18977d62b00eSchristos    ctf_dedup_emit afterwards to do that.  */
18987d62b00eSchristos 
18997d62b00eSchristos int
1900*6881a400Schristos ctf_dedup (ctf_dict_t *output, ctf_dict_t **inputs, uint32_t ninputs,
19017d62b00eSchristos 	   uint32_t *parents, int cu_mapped)
19027d62b00eSchristos {
19037d62b00eSchristos   ctf_dedup_t *d = &output->ctf_dedup;
19047d62b00eSchristos   size_t i;
19057d62b00eSchristos   ctf_next_t *it = NULL;
19067d62b00eSchristos 
19077d62b00eSchristos   if (ctf_dedup_init (output) < 0)
19087d62b00eSchristos     return -1; 					/* errno is set for us.  */
19097d62b00eSchristos 
1910*6881a400Schristos   for (i = 0; i < ninputs; i++)
1911*6881a400Schristos     {
1912*6881a400Schristos       ctf_dprintf ("Input %i: %s\n", (int) i, ctf_link_input_name (inputs[i]));
1913*6881a400Schristos       if (ctf_dynhash_insert (d->cd_input_nums, inputs[i],
1914*6881a400Schristos 			      (void *) (uintptr_t) i) < 0)
1915*6881a400Schristos 	{
1916*6881a400Schristos 	  ctf_set_errno (output, errno);
1917*6881a400Schristos 	  ctf_err_warn (output, 0, errno, _("ctf_dedup: cannot initialize: %s\n"),
1918*6881a400Schristos 			ctf_errmsg (errno));
1919*6881a400Schristos 	  goto err;
1920*6881a400Schristos 	}
1921*6881a400Schristos     }
1922*6881a400Schristos 
19237d62b00eSchristos   /* Some flags do not apply when CU-mapping: this is not a duplicated link,
19247d62b00eSchristos      because there is only one output and we really don't want to end up marking
19257d62b00eSchristos      all nonconflicting but appears-only-once types as conflicting (which in the
19267d62b00eSchristos      CU-mapped link means we'd mark them all as non-root-visible!).  */
19277d62b00eSchristos   d->cd_link_flags = output->ctf_link_flags;
19287d62b00eSchristos   if (cu_mapped)
19297d62b00eSchristos     d->cd_link_flags &= ~(CTF_LINK_SHARE_DUPLICATED);
19307d62b00eSchristos 
19317d62b00eSchristos   /* Compute hash values for all types, recursively, treating child structures
19327d62b00eSchristos      and unions equivalent to forwards, and hashing in the name of the referent
19337d62b00eSchristos      of each such type into structures, unions, and non-opaque forwards.
19347d62b00eSchristos      Populate a mapping from decorated name (including an indication of
19357d62b00eSchristos      struct/union/enum namespace) to count of type hash values in
19367d62b00eSchristos      cd_name_counts, a mapping from and a mapping from hash values to input type
19377d62b00eSchristos      IDs in cd_output_mapping.  */
19387d62b00eSchristos 
19397d62b00eSchristos   ctf_dprintf ("Computing type hashes\n");
19407d62b00eSchristos   for (i = 0; i < ninputs; i++)
19417d62b00eSchristos     {
19427d62b00eSchristos       ctf_id_t id;
19437d62b00eSchristos 
19447d62b00eSchristos       while ((id = ctf_type_next (inputs[i], &it, NULL, 1)) != CTF_ERR)
19457d62b00eSchristos 	{
1946*6881a400Schristos 	  if (ctf_dedup_hash_type (output, inputs[i], inputs,
1947*6881a400Schristos 				   parents, i, id, 0, 0,
1948*6881a400Schristos 				   ctf_dedup_populate_mappings) == NULL)
1949*6881a400Schristos 	    goto err;				/* errno is set for us.  */
19507d62b00eSchristos 	}
19517d62b00eSchristos       if (ctf_errno (inputs[i]) != ECTF_NEXT_END)
19527d62b00eSchristos 	{
19537d62b00eSchristos 	  ctf_set_errno (output, ctf_errno (inputs[i]));
19547d62b00eSchristos 	  ctf_err_warn (output, 0, 0, _("iteration failure "
19557d62b00eSchristos 					"computing type hashes"));
1956*6881a400Schristos 	  goto err;
19577d62b00eSchristos 	}
19587d62b00eSchristos     }
19597d62b00eSchristos 
19607d62b00eSchristos   /* Go through the cd_name_counts name->hash->count mapping for all CTF
19617d62b00eSchristos      namespaces: any name with many hashes associated with it at this stage is
19627d62b00eSchristos      necessarily ambiguous.  Mark all the hashes except the most common as
19637d62b00eSchristos      conflicting in the output.  */
19647d62b00eSchristos 
19657d62b00eSchristos   ctf_dprintf ("Detecting type name ambiguity\n");
19667d62b00eSchristos   if (ctf_dedup_detect_name_ambiguity (output, inputs) < 0)
1967*6881a400Schristos       goto err;					/* errno is set for us.  */
19687d62b00eSchristos 
19697d62b00eSchristos   /* If the link mode is CTF_LINK_SHARE_DUPLICATED, we change any unconflicting
19707d62b00eSchristos      types whose output mapping references only one input dict into a
19717d62b00eSchristos      conflicting type, so that they end up in the per-CU dictionaries.  */
19727d62b00eSchristos 
19737d62b00eSchristos   if (d->cd_link_flags & CTF_LINK_SHARE_DUPLICATED)
19747d62b00eSchristos     {
19757d62b00eSchristos       ctf_dprintf ("Conflictifying unshared types\n");
19767d62b00eSchristos       if (ctf_dedup_conflictify_unshared (output, inputs) < 0)
1977*6881a400Schristos 	goto err;				/* errno is set for us.  */
19787d62b00eSchristos     }
19797d62b00eSchristos   return 0;
1980*6881a400Schristos 
1981*6881a400Schristos  err:
1982*6881a400Schristos   ctf_dedup_fini (output, NULL, 0);
1983*6881a400Schristos   return -1;
19847d62b00eSchristos }
19857d62b00eSchristos 
19867d62b00eSchristos static int
1987*6881a400Schristos ctf_dedup_rwalk_output_mapping (ctf_dict_t *output, ctf_dict_t **inputs,
19887d62b00eSchristos 				uint32_t ninputs, uint32_t *parents,
19897d62b00eSchristos 				ctf_dynset_t *already_visited,
19907d62b00eSchristos 				const char *hval,
19917d62b00eSchristos 				int (*visit_fun) (const char *hval,
1992*6881a400Schristos 						  ctf_dict_t *output,
1993*6881a400Schristos 						  ctf_dict_t **inputs,
19947d62b00eSchristos 						  uint32_t ninputs,
19957d62b00eSchristos 						  uint32_t *parents,
19967d62b00eSchristos 						  int already_visited,
1997*6881a400Schristos 						  ctf_dict_t *input,
19987d62b00eSchristos 						  ctf_id_t type,
19997d62b00eSchristos 						  void *id,
20007d62b00eSchristos 						  int depth,
20017d62b00eSchristos 						  void *arg),
20027d62b00eSchristos 				void *arg, unsigned long depth);
20037d62b00eSchristos 
20047d62b00eSchristos /* Like ctf_dedup_rwalk_output_mapping (which see), only takes a single target
20057d62b00eSchristos    type and visits it.  */
20067d62b00eSchristos static int
2007*6881a400Schristos ctf_dedup_rwalk_one_output_mapping (ctf_dict_t *output,
2008*6881a400Schristos 				    ctf_dict_t **inputs, uint32_t ninputs,
20097d62b00eSchristos 				    uint32_t *parents,
20107d62b00eSchristos 				    ctf_dynset_t *already_visited,
20117d62b00eSchristos 				    int visited, void *type_id,
20127d62b00eSchristos 				    const char *hval,
20137d62b00eSchristos 				    int (*visit_fun) (const char *hval,
2014*6881a400Schristos 						      ctf_dict_t *output,
2015*6881a400Schristos 						      ctf_dict_t **inputs,
20167d62b00eSchristos 						      uint32_t ninputs,
20177d62b00eSchristos 						      uint32_t *parents,
20187d62b00eSchristos 						      int already_visited,
2019*6881a400Schristos 						      ctf_dict_t *input,
20207d62b00eSchristos 						      ctf_id_t type,
20217d62b00eSchristos 						      void *id,
20227d62b00eSchristos 						      int depth,
20237d62b00eSchristos 						      void *arg),
20247d62b00eSchristos 				    void *arg, unsigned long depth)
20257d62b00eSchristos {
20267d62b00eSchristos   ctf_dedup_t *d = &output->ctf_dedup;
2027*6881a400Schristos   ctf_dict_t *fp;
20287d62b00eSchristos   int input_num;
20297d62b00eSchristos   ctf_id_t type;
20307d62b00eSchristos   int ret;
20317d62b00eSchristos   const char *whaterr;
20327d62b00eSchristos 
20337d62b00eSchristos   input_num = CTF_DEDUP_GID_TO_INPUT (type_id);
20347d62b00eSchristos   fp = inputs[input_num];
20357d62b00eSchristos   type = CTF_DEDUP_GID_TO_TYPE (type_id);
20367d62b00eSchristos 
20377d62b00eSchristos   ctf_dprintf ("%lu: Starting walk over type %s, %i/%lx (%p), from %s, "
20387d62b00eSchristos 	       "kind %i\n", depth, hval, input_num, type, (void *) fp,
20397d62b00eSchristos 	       ctf_link_input_name (fp), ctf_type_kind_unsliced (fp, type));
20407d62b00eSchristos 
20417d62b00eSchristos   /* Get the single call we do if this type has already been visited out of the
20427d62b00eSchristos      way.  */
20437d62b00eSchristos   if (visited)
20447d62b00eSchristos     return visit_fun (hval, output, inputs, ninputs, parents, visited, fp,
20457d62b00eSchristos 		      type, type_id, depth, arg);
20467d62b00eSchristos 
20477d62b00eSchristos   /* This macro is really ugly, but the alternative is repeating this code many
20487d62b00eSchristos      times, which is worse.  */
20497d62b00eSchristos 
20507d62b00eSchristos #define CTF_TYPE_WALK(type, errlabel, errmsg)				\
2051*6881a400Schristos   do									\
2052*6881a400Schristos     {									\
20537d62b00eSchristos       void *type_id;							\
20547d62b00eSchristos       const char *hashval;						\
20557d62b00eSchristos       int cited_type_input_num = input_num;				\
20567d62b00eSchristos 									\
20577d62b00eSchristos       if ((fp->ctf_flags & LCTF_CHILD) && (LCTF_TYPE_ISPARENT (fp, type))) \
20587d62b00eSchristos 	cited_type_input_num = parents[input_num];			\
20597d62b00eSchristos 									\
20607d62b00eSchristos       type_id = CTF_DEDUP_GID (output, cited_type_input_num, type);	\
20617d62b00eSchristos 									\
20627d62b00eSchristos       if (type == 0)							\
20637d62b00eSchristos 	{								\
20647d62b00eSchristos 	  ctf_dprintf ("Walking: unimplemented type\n");		\
20657d62b00eSchristos 	  break;							\
20667d62b00eSchristos 	}								\
20677d62b00eSchristos 									\
20687d62b00eSchristos       ctf_dprintf ("Looking up ID %i/%lx in type hashes\n",		\
20697d62b00eSchristos 		   cited_type_input_num, type);				\
20707d62b00eSchristos       hashval = ctf_dynhash_lookup (d->cd_type_hashes, type_id);	\
20717d62b00eSchristos       if (!ctf_assert (output, hashval))				\
20727d62b00eSchristos 	{								\
20737d62b00eSchristos 	  whaterr = N_("error looking up ID in type hashes");		\
20747d62b00eSchristos 	  goto errlabel;						\
20757d62b00eSchristos 	}								\
20767d62b00eSchristos       ctf_dprintf ("ID %i/%lx has hash %s\n", cited_type_input_num, type, \
20777d62b00eSchristos 		   hashval);						\
20787d62b00eSchristos 									\
20797d62b00eSchristos       ret = ctf_dedup_rwalk_output_mapping (output, inputs, ninputs, parents, \
20807d62b00eSchristos 					    already_visited, hashval,	\
20817d62b00eSchristos 					    visit_fun, arg, depth);	\
20827d62b00eSchristos       if (ret < 0)							\
20837d62b00eSchristos 	{								\
20847d62b00eSchristos 	  whaterr = errmsg;						\
20857d62b00eSchristos 	  goto errlabel;						\
20867d62b00eSchristos 	}								\
2087*6881a400Schristos     }									\
2088*6881a400Schristos   while (0)
20897d62b00eSchristos 
20907d62b00eSchristos   switch (ctf_type_kind_unsliced (fp, type))
20917d62b00eSchristos     {
20927d62b00eSchristos     case CTF_K_UNKNOWN:
20937d62b00eSchristos     case CTF_K_FORWARD:
20947d62b00eSchristos     case CTF_K_INTEGER:
20957d62b00eSchristos     case CTF_K_FLOAT:
20967d62b00eSchristos     case CTF_K_ENUM:
20977d62b00eSchristos       /* No types referenced.  */
20987d62b00eSchristos       break;
20997d62b00eSchristos 
21007d62b00eSchristos     case CTF_K_TYPEDEF:
21017d62b00eSchristos     case CTF_K_VOLATILE:
21027d62b00eSchristos     case CTF_K_CONST:
21037d62b00eSchristos     case CTF_K_RESTRICT:
21047d62b00eSchristos     case CTF_K_POINTER:
21057d62b00eSchristos     case CTF_K_SLICE:
21067d62b00eSchristos       CTF_TYPE_WALK (ctf_type_reference (fp, type), err,
21077d62b00eSchristos 		     N_("error during referenced type walk"));
21087d62b00eSchristos       break;
21097d62b00eSchristos 
21107d62b00eSchristos     case CTF_K_ARRAY:
21117d62b00eSchristos       {
21127d62b00eSchristos 	ctf_arinfo_t ar;
21137d62b00eSchristos 
21147d62b00eSchristos 	if (ctf_array_info (fp, type, &ar) < 0)
21157d62b00eSchristos 	  {
21167d62b00eSchristos 	    whaterr = N_("error during array info lookup");
21177d62b00eSchristos 	    goto err_msg;
21187d62b00eSchristos 	  }
21197d62b00eSchristos 
21207d62b00eSchristos 	CTF_TYPE_WALK (ar.ctr_contents, err,
21217d62b00eSchristos 		       N_("error during array contents type walk"));
21227d62b00eSchristos 	CTF_TYPE_WALK (ar.ctr_index, err,
21237d62b00eSchristos 		       N_("error during array index type walk"));
21247d62b00eSchristos 	break;
21257d62b00eSchristos       }
21267d62b00eSchristos 
21277d62b00eSchristos     case CTF_K_FUNCTION:
21287d62b00eSchristos       {
21297d62b00eSchristos 	ctf_funcinfo_t fi;
21307d62b00eSchristos 	ctf_id_t *args;
21317d62b00eSchristos 	uint32_t j;
21327d62b00eSchristos 
21337d62b00eSchristos 	if (ctf_func_type_info (fp, type, &fi) < 0)
21347d62b00eSchristos 	  {
21357d62b00eSchristos 	    whaterr = N_("error during func type info lookup");
21367d62b00eSchristos 	    goto err_msg;
21377d62b00eSchristos 	  }
21387d62b00eSchristos 
21397d62b00eSchristos 	CTF_TYPE_WALK (fi.ctc_return, err,
21407d62b00eSchristos 		       N_("error during func return type walk"));
21417d62b00eSchristos 
21427d62b00eSchristos 	if ((args = calloc (fi.ctc_argc, sizeof (ctf_id_t))) == NULL)
21437d62b00eSchristos 	  {
21447d62b00eSchristos 	    whaterr = N_("error doing memory allocation");
21457d62b00eSchristos 	    goto err_msg;
21467d62b00eSchristos 	  }
21477d62b00eSchristos 
21487d62b00eSchristos 	if (ctf_func_type_args (fp, type, fi.ctc_argc, args) < 0)
21497d62b00eSchristos 	  {
21507d62b00eSchristos 	    whaterr = N_("error doing func arg type lookup");
21517d62b00eSchristos 	    free (args);
21527d62b00eSchristos 	    goto err_msg;
21537d62b00eSchristos 	  }
21547d62b00eSchristos 
21557d62b00eSchristos 	for (j = 0; j < fi.ctc_argc; j++)
21567d62b00eSchristos 	  CTF_TYPE_WALK (args[j], err_free_args,
21577d62b00eSchristos 			 N_("error during Func arg type walk"));
21587d62b00eSchristos 	free (args);
21597d62b00eSchristos 	break;
21607d62b00eSchristos 
21617d62b00eSchristos       err_free_args:
21627d62b00eSchristos 	free (args);
21637d62b00eSchristos 	goto err;
21647d62b00eSchristos       }
21657d62b00eSchristos     case CTF_K_STRUCT:
21667d62b00eSchristos     case CTF_K_UNION:
21677d62b00eSchristos       /* We do not recursively traverse the members of structures: they are
21687d62b00eSchristos 	 emitted later, in a separate pass.  */
21697d62b00eSchristos 	break;
21707d62b00eSchristos     default:
21717d62b00eSchristos       whaterr = N_("CTF dict corruption: unknown type kind");
21727d62b00eSchristos       goto err_msg;
21737d62b00eSchristos     }
21747d62b00eSchristos 
21757d62b00eSchristos   return visit_fun (hval, output, inputs, ninputs, parents, visited, fp, type,
21767d62b00eSchristos 		    type_id, depth, arg);
21777d62b00eSchristos 
21787d62b00eSchristos  err_msg:
21797d62b00eSchristos   ctf_set_errno (output, ctf_errno (fp));
21807d62b00eSchristos   ctf_err_warn (output, 0, 0, _("%s in input file %s at type ID %lx"),
21817d62b00eSchristos 		gettext (whaterr), ctf_link_input_name (fp), type);
21827d62b00eSchristos  err:
21837d62b00eSchristos   return -1;
21847d62b00eSchristos }
21857d62b00eSchristos /* Recursively traverse the output mapping, and do something with each type
21867d62b00eSchristos    visited, from leaves to root.  VISIT_FUN, called as recursion unwinds,
21877d62b00eSchristos    returns a negative error code or zero.  Type hashes may be visited more than
21887d62b00eSchristos    once, but are not recursed through repeatedly: ALREADY_VISITED tracks whether
21897d62b00eSchristos    types have already been visited.  */
21907d62b00eSchristos static int
2191*6881a400Schristos ctf_dedup_rwalk_output_mapping (ctf_dict_t *output, ctf_dict_t **inputs,
21927d62b00eSchristos 				uint32_t ninputs, uint32_t *parents,
21937d62b00eSchristos 				ctf_dynset_t *already_visited,
21947d62b00eSchristos 				const char *hval,
21957d62b00eSchristos 				int (*visit_fun) (const char *hval,
2196*6881a400Schristos 						  ctf_dict_t *output,
2197*6881a400Schristos 						  ctf_dict_t **inputs,
21987d62b00eSchristos 						  uint32_t ninputs,
21997d62b00eSchristos 						  uint32_t *parents,
22007d62b00eSchristos 						  int already_visited,
2201*6881a400Schristos 						  ctf_dict_t *input,
22027d62b00eSchristos 						  ctf_id_t type,
22037d62b00eSchristos 						  void *id,
22047d62b00eSchristos 						  int depth,
22057d62b00eSchristos 						  void *arg),
22067d62b00eSchristos 				void *arg, unsigned long depth)
22077d62b00eSchristos {
22087d62b00eSchristos   ctf_dedup_t *d = &output->ctf_dedup;
22097d62b00eSchristos   ctf_next_t *i = NULL;
22107d62b00eSchristos   int err;
22117d62b00eSchristos   int visited = 1;
22127d62b00eSchristos   ctf_dynset_t *type_ids;
22137d62b00eSchristos   void *id;
22147d62b00eSchristos 
22157d62b00eSchristos   depth++;
22167d62b00eSchristos 
22177d62b00eSchristos   type_ids = ctf_dynhash_lookup (d->cd_output_mapping, hval);
22187d62b00eSchristos   if (!type_ids)
22197d62b00eSchristos     {
22207d62b00eSchristos       ctf_err_warn (output, 0, ECTF_INTERNAL,
22217d62b00eSchristos 		    _("looked up type kind by nonexistent hash %s"), hval);
22227d62b00eSchristos       return ctf_set_errno (output, ECTF_INTERNAL);
22237d62b00eSchristos     }
22247d62b00eSchristos 
22257d62b00eSchristos   /* Have we seen this type before?  */
22267d62b00eSchristos 
22277d62b00eSchristos   if (!ctf_dynset_exists (already_visited, hval, NULL))
22287d62b00eSchristos     {
22297d62b00eSchristos       /* Mark as already-visited immediately, to eliminate the possibility of
22307d62b00eSchristos 	 cycles: but remember we have not actually visited it yet for the
22317d62b00eSchristos 	 upcoming call to the visit_fun.  (All our callers handle cycles
22327d62b00eSchristos 	 properly themselves, so we can just abort them aggressively as soon as
22337d62b00eSchristos 	 we find ourselves in one.)  */
22347d62b00eSchristos 
22357d62b00eSchristos       visited = 0;
22367d62b00eSchristos       if (ctf_dynset_cinsert (already_visited, hval) < 0)
22377d62b00eSchristos 	{
22387d62b00eSchristos 	  ctf_err_warn (output, 0, ENOMEM,
22397d62b00eSchristos 			_("out of memory tracking already-visited types"));
22407d62b00eSchristos 	  return ctf_set_errno (output, ENOMEM);
22417d62b00eSchristos 	}
22427d62b00eSchristos     }
22437d62b00eSchristos 
22447d62b00eSchristos   /* If this type is marked conflicted, traverse members and call
22457d62b00eSchristos      ctf_dedup_rwalk_output_mapping_once on all the unique ones: otherwise, just
22467d62b00eSchristos      pick a random one and use it.  */
22477d62b00eSchristos 
22487d62b00eSchristos   if (!ctf_dynset_exists (d->cd_conflicting_types, hval, NULL))
22497d62b00eSchristos     {
22507d62b00eSchristos       id = ctf_dynset_lookup_any (type_ids);
22517d62b00eSchristos       if (!ctf_assert (output, id))
22527d62b00eSchristos 	return -1;
22537d62b00eSchristos 
22547d62b00eSchristos       return ctf_dedup_rwalk_one_output_mapping (output, inputs, ninputs,
22557d62b00eSchristos 						 parents, already_visited,
22567d62b00eSchristos 						 visited, id, hval, visit_fun,
22577d62b00eSchristos 						 arg, depth);
22587d62b00eSchristos     }
22597d62b00eSchristos 
22607d62b00eSchristos   while ((err = ctf_dynset_next (type_ids, &i, &id)) == 0)
22617d62b00eSchristos     {
22627d62b00eSchristos       int ret;
22637d62b00eSchristos 
22647d62b00eSchristos       ret = ctf_dedup_rwalk_one_output_mapping (output, inputs, ninputs,
22657d62b00eSchristos 						parents, already_visited,
22667d62b00eSchristos 						visited, id, hval,
22677d62b00eSchristos 						visit_fun, arg, depth);
22687d62b00eSchristos       if (ret < 0)
22697d62b00eSchristos 	{
22707d62b00eSchristos 	  ctf_next_destroy (i);
22717d62b00eSchristos 	  return ret;				/* errno is set for us.  */
22727d62b00eSchristos 	}
22737d62b00eSchristos     }
22747d62b00eSchristos   if (err != ECTF_NEXT_END)
22757d62b00eSchristos     {
22767d62b00eSchristos       ctf_err_warn (output, 0, err, _("cannot walk conflicted type"));
22777d62b00eSchristos       return ctf_set_errno (output, err);
22787d62b00eSchristos     }
22797d62b00eSchristos 
22807d62b00eSchristos   return 0;
22817d62b00eSchristos }
22827d62b00eSchristos 
22837d62b00eSchristos typedef struct ctf_sort_om_cb_arg
22847d62b00eSchristos {
2285*6881a400Schristos   ctf_dict_t **inputs;
22867d62b00eSchristos   uint32_t ninputs;
22877d62b00eSchristos   ctf_dedup_t *d;
22887d62b00eSchristos } ctf_sort_om_cb_arg_t;
22897d62b00eSchristos 
22907d62b00eSchristos /* Sort the output mapping into order: types first appearing in earlier inputs
22917d62b00eSchristos    first, parents preceding children: if types first appear in the same input,
22927d62b00eSchristos    sort those with earlier ctf_id_t's first.  */
22937d62b00eSchristos static int
22947d62b00eSchristos sort_output_mapping (const ctf_next_hkv_t *one, const ctf_next_hkv_t *two,
22957d62b00eSchristos 		     void *arg_)
22967d62b00eSchristos {
22977d62b00eSchristos   ctf_sort_om_cb_arg_t *arg = (ctf_sort_om_cb_arg_t *) arg_;
22987d62b00eSchristos   ctf_dedup_t *d = arg->d;
22997d62b00eSchristos   const char *one_hval = (const char *) one->hkv_key;
23007d62b00eSchristos   const char *two_hval = (const char *) two->hkv_key;
23017d62b00eSchristos   void *one_gid, *two_gid;
23027d62b00eSchristos   uint32_t one_ninput;
23037d62b00eSchristos   uint32_t two_ninput;
2304*6881a400Schristos   ctf_dict_t *one_fp;
2305*6881a400Schristos   ctf_dict_t *two_fp;
23067d62b00eSchristos   ctf_id_t one_type;
23077d62b00eSchristos   ctf_id_t two_type;
23087d62b00eSchristos 
23097d62b00eSchristos   one_gid = ctf_dynhash_lookup (d->cd_output_first_gid, one_hval);
23107d62b00eSchristos   two_gid = ctf_dynhash_lookup (d->cd_output_first_gid, two_hval);
23117d62b00eSchristos 
23127d62b00eSchristos   one_ninput = CTF_DEDUP_GID_TO_INPUT (one_gid);
23137d62b00eSchristos   two_ninput = CTF_DEDUP_GID_TO_INPUT (two_gid);
23147d62b00eSchristos 
23157d62b00eSchristos   one_type = CTF_DEDUP_GID_TO_TYPE (one_gid);
23167d62b00eSchristos   two_type = CTF_DEDUP_GID_TO_TYPE (two_gid);
23177d62b00eSchristos 
23187d62b00eSchristos   /* It's kind of hard to smuggle an assertion failure out of here.  */
23197d62b00eSchristos   assert (one_ninput < arg->ninputs && two_ninput < arg->ninputs);
23207d62b00eSchristos 
23217d62b00eSchristos   one_fp = arg->inputs[one_ninput];
23227d62b00eSchristos   two_fp = arg->inputs[two_ninput];
23237d62b00eSchristos 
23247d62b00eSchristos   /* Parents before children.  */
23257d62b00eSchristos 
23267d62b00eSchristos   if (!(one_fp->ctf_flags & LCTF_CHILD)
23277d62b00eSchristos       && (two_fp->ctf_flags & LCTF_CHILD))
23287d62b00eSchristos     return -1;
23297d62b00eSchristos   else if ((one_fp->ctf_flags & LCTF_CHILD)
23307d62b00eSchristos       && !(two_fp->ctf_flags & LCTF_CHILD))
23317d62b00eSchristos     return 1;
23327d62b00eSchristos 
23337d62b00eSchristos   /* ninput order, types appearing in earlier TUs first.  */
23347d62b00eSchristos 
23357d62b00eSchristos   if (one_ninput < two_ninput)
23367d62b00eSchristos     return -1;
23377d62b00eSchristos   else if (two_ninput < one_ninput)
23387d62b00eSchristos     return 1;
23397d62b00eSchristos 
23407d62b00eSchristos   /* Same TU.  Earliest ctf_id_t first.  They cannot be the same.  */
23417d62b00eSchristos 
23427d62b00eSchristos   assert (one_type != two_type);
23437d62b00eSchristos   if (one_type < two_type)
23447d62b00eSchristos     return -1;
23457d62b00eSchristos   else
23467d62b00eSchristos     return 1;
23477d62b00eSchristos }
23487d62b00eSchristos 
23497d62b00eSchristos /* The public entry point to ctf_dedup_rwalk_output_mapping, above.  */
23507d62b00eSchristos static int
2351*6881a400Schristos ctf_dedup_walk_output_mapping (ctf_dict_t *output, ctf_dict_t **inputs,
23527d62b00eSchristos 			       uint32_t ninputs, uint32_t *parents,
23537d62b00eSchristos 			       int (*visit_fun) (const char *hval,
2354*6881a400Schristos 						 ctf_dict_t *output,
2355*6881a400Schristos 						 ctf_dict_t **inputs,
23567d62b00eSchristos 						 uint32_t ninputs,
23577d62b00eSchristos 						 uint32_t *parents,
23587d62b00eSchristos 						 int already_visited,
2359*6881a400Schristos 						 ctf_dict_t *input,
23607d62b00eSchristos 						 ctf_id_t type,
23617d62b00eSchristos 						 void *id,
23627d62b00eSchristos 						 int depth,
23637d62b00eSchristos 						 void *arg),
23647d62b00eSchristos 			       void *arg)
23657d62b00eSchristos {
23667d62b00eSchristos   ctf_dynset_t *already_visited;
23677d62b00eSchristos   ctf_next_t *i = NULL;
23687d62b00eSchristos   ctf_sort_om_cb_arg_t sort_arg;
23697d62b00eSchristos   int err;
23707d62b00eSchristos   void *k;
23717d62b00eSchristos 
23727d62b00eSchristos   if ((already_visited = ctf_dynset_create (htab_hash_string,
2373*6881a400Schristos 					    htab_eq_string,
23747d62b00eSchristos 					    NULL)) == NULL)
23757d62b00eSchristos     return ctf_set_errno (output, ENOMEM);
23767d62b00eSchristos 
23777d62b00eSchristos   sort_arg.inputs = inputs;
23787d62b00eSchristos   sort_arg.ninputs = ninputs;
23797d62b00eSchristos   sort_arg.d = &output->ctf_dedup;
23807d62b00eSchristos 
23817d62b00eSchristos   while ((err = ctf_dynhash_next_sorted (output->ctf_dedup.cd_output_mapping,
23827d62b00eSchristos 					 &i, &k, NULL, sort_output_mapping,
23837d62b00eSchristos 					 &sort_arg)) == 0)
23847d62b00eSchristos     {
23857d62b00eSchristos       const char *hval = (const char *) k;
23867d62b00eSchristos 
23877d62b00eSchristos       err = ctf_dedup_rwalk_output_mapping (output, inputs, ninputs, parents,
23887d62b00eSchristos 					    already_visited, hval, visit_fun,
23897d62b00eSchristos 					    arg, 0);
23907d62b00eSchristos       if (err < 0)
23917d62b00eSchristos 	{
23927d62b00eSchristos 	  ctf_next_destroy (i);
23937d62b00eSchristos 	  goto err;				/* errno is set for us.  */
23947d62b00eSchristos 	}
23957d62b00eSchristos     }
23967d62b00eSchristos   if (err != ECTF_NEXT_END)
23977d62b00eSchristos     {
23987d62b00eSchristos       ctf_err_warn (output, 0, err, _("cannot recurse over output mapping"));
23997d62b00eSchristos       ctf_set_errno (output, err);
24007d62b00eSchristos       goto err;
24017d62b00eSchristos     }
24027d62b00eSchristos   ctf_dynset_destroy (already_visited);
24037d62b00eSchristos 
24047d62b00eSchristos   return 0;
24057d62b00eSchristos  err:
24067d62b00eSchristos   ctf_dynset_destroy (already_visited);
24077d62b00eSchristos   return -1;
24087d62b00eSchristos }
24097d62b00eSchristos 
24107d62b00eSchristos /* Possibly synthesise a synthetic forward in TARGET to subsitute for a
24117d62b00eSchristos    conflicted per-TU type ID in INPUT with hash HVAL.  Return its CTF ID, or 0
24127d62b00eSchristos    if none was needed.  */
24137d62b00eSchristos static ctf_id_t
2414*6881a400Schristos ctf_dedup_maybe_synthesize_forward (ctf_dict_t *output, ctf_dict_t *target,
2415*6881a400Schristos 				    ctf_dict_t *input, ctf_id_t id,
24167d62b00eSchristos 				    const char *hval)
24177d62b00eSchristos {
24187d62b00eSchristos   ctf_dedup_t *od = &output->ctf_dedup;
24197d62b00eSchristos   ctf_dedup_t *td = &target->ctf_dedup;
24207d62b00eSchristos   int kind;
24217d62b00eSchristos   int fwdkind;
2422*6881a400Schristos   const char *name = ctf_type_name_raw (input, id);
24237d62b00eSchristos   const char *decorated;
24247d62b00eSchristos   void *v;
24257d62b00eSchristos   ctf_id_t emitted_forward;
24267d62b00eSchristos 
24277d62b00eSchristos   if (!ctf_dynset_exists (od->cd_conflicting_types, hval, NULL)
24287d62b00eSchristos       || target->ctf_flags & LCTF_CHILD
2429*6881a400Schristos       || name[0] == '\0'
24307d62b00eSchristos       || (((kind = ctf_type_kind_unsliced (input, id)) != CTF_K_STRUCT
24317d62b00eSchristos 	   && kind != CTF_K_UNION && kind != CTF_K_FORWARD)))
24327d62b00eSchristos     return 0;
24337d62b00eSchristos 
24347d62b00eSchristos   fwdkind = ctf_type_kind_forwarded (input, id);
24357d62b00eSchristos 
24367d62b00eSchristos   ctf_dprintf ("Using synthetic forward for conflicted struct/union with "
24377d62b00eSchristos 	       "hval %s\n", hval);
24387d62b00eSchristos 
24397d62b00eSchristos   if (!ctf_assert (output, name))
24407d62b00eSchristos     return CTF_ERR;
24417d62b00eSchristos 
24427d62b00eSchristos   if ((decorated = ctf_decorate_type_name (output, name, fwdkind)) == NULL)
24437d62b00eSchristos     return CTF_ERR;
24447d62b00eSchristos 
24457d62b00eSchristos   if (!ctf_dynhash_lookup_kv (td->cd_output_emission_conflicted_forwards,
24467d62b00eSchristos 			      decorated, NULL, &v))
24477d62b00eSchristos     {
24487d62b00eSchristos       if ((emitted_forward = ctf_add_forward (target, CTF_ADD_ROOT, name,
24497d62b00eSchristos 					      fwdkind)) == CTF_ERR)
24507d62b00eSchristos 	{
24517d62b00eSchristos 	  ctf_set_errno (output, ctf_errno (target));
24527d62b00eSchristos 	  return CTF_ERR;
24537d62b00eSchristos 	}
24547d62b00eSchristos 
24557d62b00eSchristos       if (ctf_dynhash_cinsert (td->cd_output_emission_conflicted_forwards,
24567d62b00eSchristos 			       decorated, (void *) (uintptr_t)
24577d62b00eSchristos 			       emitted_forward) < 0)
24587d62b00eSchristos 	{
24597d62b00eSchristos 	  ctf_set_errno (output, ENOMEM);
24607d62b00eSchristos 	  return CTF_ERR;
24617d62b00eSchristos 	}
24627d62b00eSchristos     }
24637d62b00eSchristos   else
24647d62b00eSchristos     emitted_forward = (ctf_id_t) (uintptr_t) v;
24657d62b00eSchristos 
24667d62b00eSchristos   ctf_dprintf ("Cross-TU conflicted struct: passing back forward, %lx\n",
24677d62b00eSchristos 	       emitted_forward);
24687d62b00eSchristos 
24697d62b00eSchristos   return emitted_forward;
24707d62b00eSchristos }
24717d62b00eSchristos 
24727d62b00eSchristos /* Map a GID in some INPUT dict, in the form of an input number and a ctf_id_t,
24737d62b00eSchristos    into a GID in a target output dict.  If it returns 0, this is the
24747d62b00eSchristos    unimplemented type, and the input type must have been 0.  The OUTPUT dict is
24757d62b00eSchristos    assumed to be the parent of the TARGET, if it is not the TARGET itself.
24767d62b00eSchristos 
24777d62b00eSchristos    Returns CTF_ERR on failure.  Responds to an incoming CTF_ERR as an 'id' by
24787d62b00eSchristos    returning CTF_ERR, to simplify callers.  Errors are always propagated to the
24797d62b00eSchristos    input, even if they relate to the target, for the same reason.  (Target
24807d62b00eSchristos    errors are expected to be very rare.)
24817d62b00eSchristos 
24827d62b00eSchristos    If the type in question is a citation of a conflicted type in a different TU,
24837d62b00eSchristos    emit a forward of the right type in its place (if not already emitted), and
24847d62b00eSchristos    record that forward in cd_output_emission_conflicted_forwards.  This avoids
24857d62b00eSchristos    the need to replicate the entire type graph below this point in the current
24867d62b00eSchristos    TU (an appalling waste of space).
24877d62b00eSchristos 
24887d62b00eSchristos    TODO: maybe replace forwards in the same TU with their referents?  Might
24897d62b00eSchristos    make usability a bit better.  */
24907d62b00eSchristos 
24917d62b00eSchristos static ctf_id_t
2492*6881a400Schristos ctf_dedup_id_to_target (ctf_dict_t *output, ctf_dict_t *target,
2493*6881a400Schristos 			ctf_dict_t **inputs, uint32_t ninputs,
2494*6881a400Schristos 			uint32_t *parents, ctf_dict_t *input, int input_num,
24957d62b00eSchristos 			ctf_id_t id)
24967d62b00eSchristos {
24977d62b00eSchristos   ctf_dedup_t *od = &output->ctf_dedup;
24987d62b00eSchristos   ctf_dedup_t *td = &target->ctf_dedup;
2499*6881a400Schristos   ctf_dict_t *err_fp = input;
25007d62b00eSchristos   const char *hval;
25017d62b00eSchristos   void *target_id;
25027d62b00eSchristos   ctf_id_t emitted_forward;
25037d62b00eSchristos 
25047d62b00eSchristos   /* The target type of an error is an error.  */
25057d62b00eSchristos   if (id == CTF_ERR)
25067d62b00eSchristos     return CTF_ERR;
25077d62b00eSchristos 
25087d62b00eSchristos   /* The unimplemented type's ID never changes.  */
25097d62b00eSchristos   if (!id)
25107d62b00eSchristos     {
25117d62b00eSchristos       ctf_dprintf ("%i/%lx: unimplemented type\n", input_num, id);
25127d62b00eSchristos       return 0;
25137d62b00eSchristos     }
25147d62b00eSchristos 
25157d62b00eSchristos   ctf_dprintf ("Mapping %i/%lx to target %p (%s)\n", input_num,
25167d62b00eSchristos 	       id, (void *) target, ctf_link_input_name (target));
25177d62b00eSchristos 
25187d62b00eSchristos   /* If the input type is in the parent type space, and this is a child, reset
25197d62b00eSchristos      the input to the parent (which must already have been emitted, since
25207d62b00eSchristos      emission of parent dicts happens before children).  */
25217d62b00eSchristos   if ((input->ctf_flags & LCTF_CHILD) && (LCTF_TYPE_ISPARENT (input, id)))
25227d62b00eSchristos     {
25237d62b00eSchristos       if (!ctf_assert (output, parents[input_num] <= ninputs))
25247d62b00eSchristos 	return -1;
25257d62b00eSchristos       input = inputs[parents[input_num]];
25267d62b00eSchristos       input_num = parents[input_num];
25277d62b00eSchristos     }
25287d62b00eSchristos 
25297d62b00eSchristos   hval = ctf_dynhash_lookup (od->cd_type_hashes,
25307d62b00eSchristos 			     CTF_DEDUP_GID (output, input_num, id));
25317d62b00eSchristos 
25327d62b00eSchristos   if (!ctf_assert (output, hval && td->cd_output_emission_hashes))
25337d62b00eSchristos     return -1;
25347d62b00eSchristos 
25357d62b00eSchristos   /* If this type is a conflicted tagged structure, union, or forward,
25367d62b00eSchristos      substitute a synthetic forward instead, emitting it if need be.  Only do
25377d62b00eSchristos      this if the target is in the parent dict: if it's in the child dict, we can
25387d62b00eSchristos      just point straight at the thing itself.  Of course, we might be looking in
25397d62b00eSchristos      the child dict right now and not find it and have to look in the parent, so
25407d62b00eSchristos      we have to do this check twice.  */
25417d62b00eSchristos 
25427d62b00eSchristos   emitted_forward = ctf_dedup_maybe_synthesize_forward (output, target,
25437d62b00eSchristos 							input, id, hval);
25447d62b00eSchristos   switch (emitted_forward)
25457d62b00eSchristos     {
25467d62b00eSchristos     case 0: /* No forward needed.  */
25477d62b00eSchristos       break;
25487d62b00eSchristos     case -1:
25497d62b00eSchristos       ctf_set_errno (err_fp, ctf_errno (output));
25507d62b00eSchristos       ctf_err_warn (err_fp, 0, 0, _("cannot add synthetic forward for type "
25517d62b00eSchristos 				    "%i/%lx"), input_num, id);
25527d62b00eSchristos       return -1;
25537d62b00eSchristos     default:
25547d62b00eSchristos       return emitted_forward;
25557d62b00eSchristos     }
25567d62b00eSchristos 
25577d62b00eSchristos   ctf_dprintf ("Looking up %i/%lx, hash %s, in target\n", input_num, id, hval);
25587d62b00eSchristos 
25597d62b00eSchristos   target_id = ctf_dynhash_lookup (td->cd_output_emission_hashes, hval);
25607d62b00eSchristos   if (!target_id)
25617d62b00eSchristos     {
25627d62b00eSchristos       /* Must be in the parent, so this must be a child, and they must not be
25637d62b00eSchristos 	 the same dict.  */
25647d62b00eSchristos       ctf_dprintf ("Checking shared parent for target\n");
25657d62b00eSchristos       if (!ctf_assert (output, (target != output)
25667d62b00eSchristos 		       && (target->ctf_flags & LCTF_CHILD)))
25677d62b00eSchristos 	return -1;
25687d62b00eSchristos 
25697d62b00eSchristos       target_id = ctf_dynhash_lookup (od->cd_output_emission_hashes, hval);
25707d62b00eSchristos 
25717d62b00eSchristos       emitted_forward = ctf_dedup_maybe_synthesize_forward (output, output,
25727d62b00eSchristos 							    input, id, hval);
25737d62b00eSchristos       switch (emitted_forward)
25747d62b00eSchristos 	{
25757d62b00eSchristos 	case 0: /* No forward needed.  */
25767d62b00eSchristos 	  break;
25777d62b00eSchristos 	case -1:
25787d62b00eSchristos 	  ctf_err_warn (err_fp, 0, ctf_errno (output),
25797d62b00eSchristos 			_("cannot add synthetic forward for type %i/%lx"),
25807d62b00eSchristos 			input_num, id);
25817d62b00eSchristos 	  return ctf_set_errno (err_fp, ctf_errno (output));
25827d62b00eSchristos 	default:
25837d62b00eSchristos 	  return emitted_forward;
25847d62b00eSchristos 	}
25857d62b00eSchristos     }
25867d62b00eSchristos   if (!ctf_assert (output, target_id))
25877d62b00eSchristos     return -1;
25887d62b00eSchristos   return (ctf_id_t) (uintptr_t) target_id;
25897d62b00eSchristos }
25907d62b00eSchristos 
25917d62b00eSchristos /* Emit a single deduplicated TYPE with the given HVAL, located in a given
25927d62b00eSchristos    INPUT, with the given (G)ID, into the shared OUTPUT or a
25937d62b00eSchristos    possibly-newly-created per-CU dict.  All the types this type depends upon
25947d62b00eSchristos    have already been emitted.  (This type itself may also have been emitted.)
25957d62b00eSchristos 
25967d62b00eSchristos    If the ARG is 1, this is a CU-mapped deduplication round mapping many
2597*6881a400Schristos    ctf_dict_t's into precisely one: conflicting types should be marked
25987d62b00eSchristos    non-root-visible.  If the ARG is 0, conflicting types go into per-CU
25997d62b00eSchristos    dictionaries stored in the input's ctf_dedup.cd_output: otherwise, everything
26007d62b00eSchristos    is emitted directly into the output.  No struct/union members are emitted.
26017d62b00eSchristos 
26027d62b00eSchristos    Optimization opportunity: trace the ancestry of non-root-visible types and
26037d62b00eSchristos    elide all that neither have a root-visible type somewhere towards their root,
26047d62b00eSchristos    nor have the type visible via any other route (the function info section,
26057d62b00eSchristos    data object section, backtrace section etc).  */
26067d62b00eSchristos 
26077d62b00eSchristos static int
2608*6881a400Schristos ctf_dedup_emit_type (const char *hval, ctf_dict_t *output, ctf_dict_t **inputs,
26097d62b00eSchristos 		     uint32_t ninputs, uint32_t *parents, int already_visited,
2610*6881a400Schristos 		     ctf_dict_t *input, ctf_id_t type, void *id, int depth,
26117d62b00eSchristos 		     void *arg)
26127d62b00eSchristos {
26137d62b00eSchristos   ctf_dedup_t *d = &output->ctf_dedup;
26147d62b00eSchristos   int kind = ctf_type_kind_unsliced (input, type);
26157d62b00eSchristos   const char *name;
2616*6881a400Schristos   ctf_dict_t *target = output;
2617*6881a400Schristos   ctf_dict_t *real_input;
26187d62b00eSchristos   const ctf_type_t *tp;
26197d62b00eSchristos   int input_num = CTF_DEDUP_GID_TO_INPUT (id);
26207d62b00eSchristos   int output_num = (uint32_t) -1;		/* 'shared' */
26217d62b00eSchristos   int cu_mapped = *(int *)arg;
26227d62b00eSchristos   int isroot = 1;
26237d62b00eSchristos   int is_conflicting;
26247d62b00eSchristos 
26257d62b00eSchristos   ctf_next_t *i = NULL;
26267d62b00eSchristos   ctf_id_t new_type;
26277d62b00eSchristos   ctf_id_t ref;
26287d62b00eSchristos   ctf_id_t maybe_dup = 0;
26297d62b00eSchristos   ctf_encoding_t ep;
26307d62b00eSchristos   const char *errtype;
26317d62b00eSchristos   int emission_hashed = 0;
26327d62b00eSchristos 
26337d62b00eSchristos   /* We don't want to re-emit something we've already emitted.  */
26347d62b00eSchristos 
26357d62b00eSchristos   if (already_visited)
26367d62b00eSchristos     return 0;
26377d62b00eSchristos 
26387d62b00eSchristos   ctf_dprintf ("%i: Emitting type with hash %s from %s: determining target\n",
26397d62b00eSchristos 	       depth, hval, ctf_link_input_name (input));
26407d62b00eSchristos 
26417d62b00eSchristos   /* Conflicting types go into a per-CU output dictionary, unless this is a
26427d62b00eSchristos      CU-mapped run.  The import is not refcounted, since it goes into the
26437d62b00eSchristos      ctf_link_outputs dict of the output that is its parent.  */
26447d62b00eSchristos   is_conflicting = ctf_dynset_exists (d->cd_conflicting_types, hval, NULL);
26457d62b00eSchristos 
26467d62b00eSchristos   if (is_conflicting && !cu_mapped)
26477d62b00eSchristos     {
26487d62b00eSchristos       ctf_dprintf ("%i: Type %s in %i/%lx is conflicted: "
26497d62b00eSchristos 		   "inserting into per-CU target.\n",
26507d62b00eSchristos 		   depth, hval, input_num, type);
26517d62b00eSchristos 
26527d62b00eSchristos       if (input->ctf_dedup.cd_output)
26537d62b00eSchristos 	target = input->ctf_dedup.cd_output;
26547d62b00eSchristos       else
26557d62b00eSchristos 	{
26567d62b00eSchristos 	  int err;
26577d62b00eSchristos 
26587d62b00eSchristos 	  if ((target = ctf_create (&err)) == NULL)
26597d62b00eSchristos 	    {
26607d62b00eSchristos 	      ctf_err_warn (output, 0, err,
26617d62b00eSchristos 			    _("cannot create per-CU CTF archive for CU %s"),
26627d62b00eSchristos 			    ctf_link_input_name (input));
26637d62b00eSchristos 	      return ctf_set_errno (output, err);
26647d62b00eSchristos 	    }
26657d62b00eSchristos 
26667d62b00eSchristos 	  ctf_import_unref (target, output);
26677d62b00eSchristos 	  if (ctf_cuname (input) != NULL)
26687d62b00eSchristos 	    ctf_cuname_set (target, ctf_cuname (input));
26697d62b00eSchristos 	  else
26707d62b00eSchristos 	    ctf_cuname_set (target, "unnamed-CU");
26717d62b00eSchristos 	  ctf_parent_name_set (target, _CTF_SECTION);
26727d62b00eSchristos 
26737d62b00eSchristos 	  input->ctf_dedup.cd_output = target;
2674*6881a400Schristos 	  input->ctf_link_in_out = target;
2675*6881a400Schristos 	  target->ctf_link_in_out = input;
26767d62b00eSchristos 	}
26777d62b00eSchristos       output_num = input_num;
26787d62b00eSchristos     }
26797d62b00eSchristos 
26807d62b00eSchristos   real_input = input;
26817d62b00eSchristos   if ((tp = ctf_lookup_by_id (&real_input, type)) == NULL)
26827d62b00eSchristos     {
26837d62b00eSchristos       ctf_err_warn (output, 0, ctf_errno (input),
26847d62b00eSchristos 		    _("%s: lookup failure for type %lx"),
26857d62b00eSchristos 		    ctf_link_input_name (real_input), type);
26867d62b00eSchristos       return ctf_set_errno (output, ctf_errno (input));
26877d62b00eSchristos     }
26887d62b00eSchristos 
26897d62b00eSchristos   name = ctf_strraw (real_input, tp->ctt_name);
26907d62b00eSchristos 
26917d62b00eSchristos   /* Hide conflicting types, if we were asked to: also hide if a type with this
26927d62b00eSchristos      name already exists and is not a forward.  */
26937d62b00eSchristos   if (cu_mapped && is_conflicting)
26947d62b00eSchristos     isroot = 0;
26957d62b00eSchristos   else if (name
26967d62b00eSchristos 	   && (maybe_dup = ctf_lookup_by_rawname (target, kind, name)) != 0)
26977d62b00eSchristos     {
26987d62b00eSchristos       if (ctf_type_kind (target, maybe_dup) != CTF_K_FORWARD)
26997d62b00eSchristos 	isroot = 0;
27007d62b00eSchristos     }
27017d62b00eSchristos 
27027d62b00eSchristos   ctf_dprintf ("%i: Emitting type with hash %s (%s), into target %i/%p\n",
27037d62b00eSchristos 	       depth, hval, name ? name : "", input_num, (void *) target);
27047d62b00eSchristos 
27057d62b00eSchristos   if (!target->ctf_dedup.cd_output_emission_hashes)
27067d62b00eSchristos     if ((target->ctf_dedup.cd_output_emission_hashes
27077d62b00eSchristos 	 = ctf_dynhash_create (ctf_hash_string, ctf_hash_eq_string,
27087d62b00eSchristos 			      NULL, NULL)) == NULL)
27097d62b00eSchristos       goto oom_hash;
27107d62b00eSchristos 
27117d62b00eSchristos   if (!target->ctf_dedup.cd_output_emission_conflicted_forwards)
27127d62b00eSchristos     if ((target->ctf_dedup.cd_output_emission_conflicted_forwards
27137d62b00eSchristos 	 = ctf_dynhash_create (ctf_hash_string, ctf_hash_eq_string,
27147d62b00eSchristos 			      NULL, NULL)) == NULL)
27157d62b00eSchristos       goto oom_hash;
27167d62b00eSchristos 
27177d62b00eSchristos   switch (kind)
27187d62b00eSchristos     {
27197d62b00eSchristos     case CTF_K_UNKNOWN:
2720*6881a400Schristos       /* These are types that CTF cannot encode, marked as such by the
2721*6881a400Schristos 	 compiler.  */
2722*6881a400Schristos       errtype = _("unknown type");
2723*6881a400Schristos       if ((new_type = ctf_add_unknown (target, isroot, name)) == CTF_ERR)
2724*6881a400Schristos 	goto err_target;
27257d62b00eSchristos       break;
27267d62b00eSchristos     case CTF_K_FORWARD:
27277d62b00eSchristos       /* This will do nothing if the type to which this forwards already exists,
27287d62b00eSchristos 	 and will be replaced with such a type if it appears later.  */
27297d62b00eSchristos 
27307d62b00eSchristos       errtype = _("forward");
27317d62b00eSchristos       if ((new_type = ctf_add_forward (target, isroot, name,
27327d62b00eSchristos 				       ctf_type_kind_forwarded (input, type)))
27337d62b00eSchristos 	  == CTF_ERR)
27347d62b00eSchristos 	goto err_target;
27357d62b00eSchristos       break;
27367d62b00eSchristos 
27377d62b00eSchristos     case CTF_K_FLOAT:
27387d62b00eSchristos     case CTF_K_INTEGER:
27397d62b00eSchristos       errtype = _("float/int");
27407d62b00eSchristos       if (ctf_type_encoding (input, type, &ep) < 0)
27417d62b00eSchristos 	goto err_input;				/* errno is set for us.  */
27427d62b00eSchristos       if ((new_type = ctf_add_encoded (target, isroot, name, &ep, kind))
27437d62b00eSchristos 	  == CTF_ERR)
27447d62b00eSchristos 	goto err_target;
27457d62b00eSchristos       break;
27467d62b00eSchristos 
27477d62b00eSchristos     case CTF_K_ENUM:
27487d62b00eSchristos       {
27497d62b00eSchristos 	int val;
27507d62b00eSchristos 	errtype = _("enum");
27517d62b00eSchristos 	if ((new_type = ctf_add_enum (target, isroot, name)) == CTF_ERR)
27527d62b00eSchristos 	  goto err_input;				/* errno is set for us.  */
27537d62b00eSchristos 
27547d62b00eSchristos 	while ((name = ctf_enum_next (input, type, &i, &val)) != NULL)
27557d62b00eSchristos 	  {
27567d62b00eSchristos 	    if (ctf_add_enumerator (target, new_type, name, val) < 0)
27577d62b00eSchristos 	      {
27587d62b00eSchristos 		ctf_err_warn (target, 0, ctf_errno (target),
27597d62b00eSchristos 			      _("%s (%i): cannot add enumeration value %s "
27607d62b00eSchristos 				"from input type %lx"),
27617d62b00eSchristos 			      ctf_link_input_name (input), input_num, name,
27627d62b00eSchristos 			      type);
27637d62b00eSchristos 		ctf_next_destroy (i);
27647d62b00eSchristos 		return ctf_set_errno (output, ctf_errno (target));
27657d62b00eSchristos 	      }
27667d62b00eSchristos 	  }
27677d62b00eSchristos 	if (ctf_errno (input) != ECTF_NEXT_END)
27687d62b00eSchristos 	  goto err_input;
27697d62b00eSchristos 	break;
27707d62b00eSchristos       }
27717d62b00eSchristos 
27727d62b00eSchristos     case CTF_K_TYPEDEF:
27737d62b00eSchristos       errtype = _("typedef");
27747d62b00eSchristos 
27757d62b00eSchristos       ref = ctf_type_reference (input, type);
27767d62b00eSchristos       if ((ref = ctf_dedup_id_to_target (output, target, inputs, ninputs,
27777d62b00eSchristos 					 parents, input, input_num,
27787d62b00eSchristos 					 ref)) == CTF_ERR)
27797d62b00eSchristos 	goto err_input;				/* errno is set for us.  */
27807d62b00eSchristos 
27817d62b00eSchristos       if ((new_type = ctf_add_typedef (target, isroot, name, ref)) == CTF_ERR)
27827d62b00eSchristos 	goto err_target;			/* errno is set for us.  */
27837d62b00eSchristos       break;
27847d62b00eSchristos 
27857d62b00eSchristos     case CTF_K_VOLATILE:
27867d62b00eSchristos     case CTF_K_CONST:
27877d62b00eSchristos     case CTF_K_RESTRICT:
27887d62b00eSchristos     case CTF_K_POINTER:
27897d62b00eSchristos       errtype = _("pointer or cvr-qual");
27907d62b00eSchristos 
27917d62b00eSchristos       ref = ctf_type_reference (input, type);
27927d62b00eSchristos       if ((ref = ctf_dedup_id_to_target (output, target, inputs, ninputs,
27937d62b00eSchristos 					 parents, input, input_num,
27947d62b00eSchristos 					 ref)) == CTF_ERR)
27957d62b00eSchristos 	goto err_input;				/* errno is set for us.  */
27967d62b00eSchristos 
27977d62b00eSchristos       if ((new_type = ctf_add_reftype (target, isroot, ref, kind)) == CTF_ERR)
27987d62b00eSchristos 	goto err_target;			/* errno is set for us.  */
27997d62b00eSchristos       break;
28007d62b00eSchristos 
28017d62b00eSchristos     case CTF_K_SLICE:
28027d62b00eSchristos       errtype = _("slice");
28037d62b00eSchristos 
28047d62b00eSchristos       if (ctf_type_encoding (input, type, &ep) < 0)
28057d62b00eSchristos 	goto err_input;				/* errno is set for us.  */
28067d62b00eSchristos 
28077d62b00eSchristos       ref = ctf_type_reference (input, type);
28087d62b00eSchristos       if ((ref = ctf_dedup_id_to_target (output, target, inputs, ninputs,
28097d62b00eSchristos 					 parents, input, input_num,
28107d62b00eSchristos 					 ref)) == CTF_ERR)
28117d62b00eSchristos 	goto err_input;
28127d62b00eSchristos 
28137d62b00eSchristos       if ((new_type = ctf_add_slice (target, isroot, ref, &ep)) == CTF_ERR)
28147d62b00eSchristos 	goto err_target;
28157d62b00eSchristos       break;
28167d62b00eSchristos 
28177d62b00eSchristos     case CTF_K_ARRAY:
28187d62b00eSchristos       {
28197d62b00eSchristos 	ctf_arinfo_t ar;
28207d62b00eSchristos 
28217d62b00eSchristos 	errtype = _("array info");
28227d62b00eSchristos 	if (ctf_array_info (input, type, &ar) < 0)
28237d62b00eSchristos 	  goto err_input;
28247d62b00eSchristos 
28257d62b00eSchristos 	ar.ctr_contents = ctf_dedup_id_to_target (output, target, inputs,
28267d62b00eSchristos 						  ninputs, parents, input,
28277d62b00eSchristos 						  input_num, ar.ctr_contents);
28287d62b00eSchristos 	ar.ctr_index = ctf_dedup_id_to_target (output, target, inputs, ninputs,
28297d62b00eSchristos 					       parents, input, input_num,
28307d62b00eSchristos 					       ar.ctr_index);
28317d62b00eSchristos 
28327d62b00eSchristos 	if (ar.ctr_contents == CTF_ERR || ar.ctr_index == CTF_ERR)
28337d62b00eSchristos 	  goto err_input;
28347d62b00eSchristos 
28357d62b00eSchristos 	if ((new_type = ctf_add_array (target, isroot, &ar)) == CTF_ERR)
28367d62b00eSchristos 	  goto err_target;
28377d62b00eSchristos 
28387d62b00eSchristos 	break;
28397d62b00eSchristos       }
28407d62b00eSchristos 
28417d62b00eSchristos     case CTF_K_FUNCTION:
28427d62b00eSchristos       {
28437d62b00eSchristos 	ctf_funcinfo_t fi;
28447d62b00eSchristos 	ctf_id_t *args;
28457d62b00eSchristos 	uint32_t j;
28467d62b00eSchristos 
28477d62b00eSchristos 	errtype = _("function");
28487d62b00eSchristos 	if (ctf_func_type_info (input, type, &fi) < 0)
28497d62b00eSchristos 	  goto err_input;
28507d62b00eSchristos 
28517d62b00eSchristos 	fi.ctc_return = ctf_dedup_id_to_target (output, target, inputs, ninputs,
28527d62b00eSchristos 						parents, input, input_num,
28537d62b00eSchristos 						fi.ctc_return);
28547d62b00eSchristos 	if (fi.ctc_return == CTF_ERR)
28557d62b00eSchristos 	  goto err_input;
28567d62b00eSchristos 
28577d62b00eSchristos 	if ((args = calloc (fi.ctc_argc, sizeof (ctf_id_t))) == NULL)
28587d62b00eSchristos 	  {
28597d62b00eSchristos 	    ctf_set_errno (input, ENOMEM);
28607d62b00eSchristos 	    goto err_input;
28617d62b00eSchristos 	  }
28627d62b00eSchristos 
28637d62b00eSchristos 	errtype = _("function args");
28647d62b00eSchristos 	if (ctf_func_type_args (input, type, fi.ctc_argc, args) < 0)
28657d62b00eSchristos 	  {
28667d62b00eSchristos 	    free (args);
28677d62b00eSchristos 	    goto err_input;
28687d62b00eSchristos 	  }
28697d62b00eSchristos 
28707d62b00eSchristos 	for (j = 0; j < fi.ctc_argc; j++)
28717d62b00eSchristos 	  {
28727d62b00eSchristos 	    args[j] = ctf_dedup_id_to_target (output, target, inputs, ninputs,
28737d62b00eSchristos 					      parents, input, input_num,
28747d62b00eSchristos 					      args[j]);
28757d62b00eSchristos 	    if (args[j] == CTF_ERR)
28767d62b00eSchristos 	      goto err_input;
28777d62b00eSchristos 	  }
28787d62b00eSchristos 
28797d62b00eSchristos 	if ((new_type = ctf_add_function (target, isroot,
28807d62b00eSchristos 					  &fi, args)) == CTF_ERR)
28817d62b00eSchristos 	  {
28827d62b00eSchristos 	    free (args);
28837d62b00eSchristos 	    goto err_target;
28847d62b00eSchristos 	  }
28857d62b00eSchristos 	free (args);
28867d62b00eSchristos 	break;
28877d62b00eSchristos       }
28887d62b00eSchristos 
28897d62b00eSchristos     case CTF_K_STRUCT:
28907d62b00eSchristos     case CTF_K_UNION:
28917d62b00eSchristos       {
28927d62b00eSchristos 	size_t size = ctf_type_size (input, type);
28937d62b00eSchristos 	void *out_id;
28947d62b00eSchristos 	/* Insert the structure itself, so other types can refer to it.  */
28957d62b00eSchristos 
28967d62b00eSchristos 	errtype = _("structure/union");
28977d62b00eSchristos 	if (kind == CTF_K_STRUCT)
28987d62b00eSchristos 	  new_type = ctf_add_struct_sized (target, isroot, name, size);
28997d62b00eSchristos 	else
29007d62b00eSchristos 	  new_type = ctf_add_union_sized (target, isroot, name, size);
29017d62b00eSchristos 
29027d62b00eSchristos 	if (new_type == CTF_ERR)
29037d62b00eSchristos 	  goto err_target;
29047d62b00eSchristos 
29057d62b00eSchristos 	out_id = CTF_DEDUP_GID (output, output_num, new_type);
29067d62b00eSchristos 	ctf_dprintf ("%i: Noting need to emit members of %p -> %p\n", depth,
29077d62b00eSchristos 		     id, out_id);
29087d62b00eSchristos 	/* Record the need to emit the members of this structure later.  */
29097d62b00eSchristos 	if (ctf_dynhash_insert (d->cd_emission_struct_members, id, out_id) < 0)
2910*6881a400Schristos 	  {
2911*6881a400Schristos 	    ctf_set_errno (target, errno);
29127d62b00eSchristos 	    goto err_target;
2913*6881a400Schristos 	  }
29147d62b00eSchristos 	break;
29157d62b00eSchristos       }
29167d62b00eSchristos     default:
29177d62b00eSchristos       ctf_err_warn (output, 0, ECTF_CORRUPT, _("%s: unknown type kind for "
29187d62b00eSchristos 					       "input type %lx"),
29197d62b00eSchristos 		    ctf_link_input_name (input), type);
29207d62b00eSchristos       return ctf_set_errno (output, ECTF_CORRUPT);
29217d62b00eSchristos     }
29227d62b00eSchristos 
29237d62b00eSchristos   if (!emission_hashed
29247d62b00eSchristos       && new_type != 0
29257d62b00eSchristos       && ctf_dynhash_cinsert (target->ctf_dedup.cd_output_emission_hashes,
29267d62b00eSchristos 			      hval, (void *) (uintptr_t) new_type) < 0)
29277d62b00eSchristos     {
29287d62b00eSchristos       ctf_err_warn (output, 0, ENOMEM, _("out of memory tracking deduplicated "
29297d62b00eSchristos 					 "global type IDs"));
29307d62b00eSchristos 	return ctf_set_errno (output, ENOMEM);
29317d62b00eSchristos     }
29327d62b00eSchristos 
29337d62b00eSchristos   if (!emission_hashed && new_type != 0)
29347d62b00eSchristos     ctf_dprintf ("%i: Inserted %s, %i/%lx -> %lx into emission hash for "
29357d62b00eSchristos 		 "target %p (%s)\n", depth, hval, input_num, type, new_type,
29367d62b00eSchristos 		 (void *) target, ctf_link_input_name (target));
29377d62b00eSchristos 
29387d62b00eSchristos   return 0;
29397d62b00eSchristos 
29407d62b00eSchristos  oom_hash:
29417d62b00eSchristos   ctf_err_warn (output, 0, ENOMEM, _("out of memory creating emission-tracking "
29427d62b00eSchristos 				     "hashes"));
29437d62b00eSchristos   return ctf_set_errno (output, ENOMEM);
29447d62b00eSchristos 
29457d62b00eSchristos  err_input:
29467d62b00eSchristos   ctf_err_warn (output, 0, ctf_errno (input),
29477d62b00eSchristos 		_("%s (%i): while emitting deduplicated %s, error getting "
29487d62b00eSchristos 		  "input type %lx"), ctf_link_input_name (input),
29497d62b00eSchristos 		input_num, errtype, type);
29507d62b00eSchristos   return ctf_set_errno (output, ctf_errno (input));
29517d62b00eSchristos  err_target:
29527d62b00eSchristos   ctf_err_warn (output, 0, ctf_errno (target),
29537d62b00eSchristos 		_("%s (%i): while emitting deduplicated %s, error emitting "
29547d62b00eSchristos 		  "target type from input type %lx"),
29557d62b00eSchristos 		ctf_link_input_name (input), input_num,
29567d62b00eSchristos 		errtype, type);
29577d62b00eSchristos   return ctf_set_errno (output, ctf_errno (target));
29587d62b00eSchristos }
29597d62b00eSchristos 
29607d62b00eSchristos /* Traverse the cd_emission_struct_members and emit the members of all
29617d62b00eSchristos    structures and unions.  All other types are emitted and complete by this
29627d62b00eSchristos    point.  */
29637d62b00eSchristos 
29647d62b00eSchristos static int
2965*6881a400Schristos ctf_dedup_emit_struct_members (ctf_dict_t *output, ctf_dict_t **inputs,
29667d62b00eSchristos 			       uint32_t ninputs, uint32_t *parents)
29677d62b00eSchristos {
29687d62b00eSchristos   ctf_dedup_t *d = &output->ctf_dedup;
29697d62b00eSchristos   ctf_next_t *i = NULL;
29707d62b00eSchristos   void *input_id, *target_id;
29717d62b00eSchristos   int err;
2972*6881a400Schristos   ctf_dict_t *err_fp, *input_fp;
29737d62b00eSchristos   int input_num;
29747d62b00eSchristos   ctf_id_t err_type;
29757d62b00eSchristos 
29767d62b00eSchristos   while ((err = ctf_dynhash_next (d->cd_emission_struct_members, &i,
29777d62b00eSchristos 				  &input_id, &target_id)) == 0)
29787d62b00eSchristos     {
29797d62b00eSchristos       ctf_next_t *j = NULL;
2980*6881a400Schristos       ctf_dict_t *target;
29817d62b00eSchristos       uint32_t target_num;
29827d62b00eSchristos       ctf_id_t input_type, target_type;
29837d62b00eSchristos       ssize_t offset;
29847d62b00eSchristos       ctf_id_t membtype;
29857d62b00eSchristos       const char *name;
29867d62b00eSchristos 
29877d62b00eSchristos       input_num = CTF_DEDUP_GID_TO_INPUT (input_id);
29887d62b00eSchristos       input_fp = inputs[input_num];
29897d62b00eSchristos       input_type = CTF_DEDUP_GID_TO_TYPE (input_id);
29907d62b00eSchristos 
29917d62b00eSchristos       /* The output is either -1 (for the shared, parent output dict) or the
29927d62b00eSchristos 	 number of the corresponding input.  */
29937d62b00eSchristos       target_num = CTF_DEDUP_GID_TO_INPUT (target_id);
29947d62b00eSchristos       if (target_num == (uint32_t) -1)
29957d62b00eSchristos 	target = output;
29967d62b00eSchristos       else
29977d62b00eSchristos 	{
29987d62b00eSchristos 	  target = inputs[target_num]->ctf_dedup.cd_output;
29997d62b00eSchristos 	  if (!ctf_assert (output, target))
30007d62b00eSchristos 	    {
30017d62b00eSchristos 	      err_fp = output;
30027d62b00eSchristos 	      err_type = input_type;
30037d62b00eSchristos 	      goto err_target;
30047d62b00eSchristos 	    }
30057d62b00eSchristos 	}
30067d62b00eSchristos       target_type = CTF_DEDUP_GID_TO_TYPE (target_id);
30077d62b00eSchristos 
30087d62b00eSchristos       while ((offset = ctf_member_next (input_fp, input_type, &j, &name,
3009*6881a400Schristos 					&membtype, 0)) >= 0)
30107d62b00eSchristos 	{
30117d62b00eSchristos 	  err_fp = target;
30127d62b00eSchristos 	  err_type = target_type;
30137d62b00eSchristos 	  if ((membtype = ctf_dedup_id_to_target (output, target, inputs,
30147d62b00eSchristos 						  ninputs, parents, input_fp,
30157d62b00eSchristos 						  input_num,
30167d62b00eSchristos 						  membtype)) == CTF_ERR)
30177d62b00eSchristos 	    {
30187d62b00eSchristos 	      ctf_next_destroy (j);
30197d62b00eSchristos 	      goto err_target;
30207d62b00eSchristos 	    }
30217d62b00eSchristos 
30227d62b00eSchristos 	  if (name == NULL)
30237d62b00eSchristos 	    name = "";
30247d62b00eSchristos #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
30257d62b00eSchristos 	  ctf_dprintf ("Emitting %s, offset %zi\n", name, offset);
30267d62b00eSchristos #endif
30277d62b00eSchristos 	  if (ctf_add_member_offset (target, target_type, name,
30287d62b00eSchristos 				     membtype, offset) < 0)
30297d62b00eSchristos 	    {
30307d62b00eSchristos 	      ctf_next_destroy (j);
30317d62b00eSchristos 	      goto err_target;
30327d62b00eSchristos 	    }
30337d62b00eSchristos 	}
30347d62b00eSchristos       if (ctf_errno (input_fp) != ECTF_NEXT_END)
30357d62b00eSchristos 	{
30367d62b00eSchristos 	  err = ctf_errno (input_fp);
30377d62b00eSchristos 	  ctf_next_destroy (i);
30387d62b00eSchristos 	  goto iterr;
30397d62b00eSchristos 	}
30407d62b00eSchristos     }
30417d62b00eSchristos   if (err != ECTF_NEXT_END)
30427d62b00eSchristos     goto iterr;
30437d62b00eSchristos 
30447d62b00eSchristos   return 0;
30457d62b00eSchristos  err_target:
30467d62b00eSchristos   ctf_next_destroy (i);
30477d62b00eSchristos   ctf_err_warn (output, 0, ctf_errno (err_fp),
30487d62b00eSchristos 		_("%s (%i): error emitting members for structure type %lx"),
30497d62b00eSchristos 		ctf_link_input_name (input_fp), input_num, err_type);
30507d62b00eSchristos   return ctf_set_errno (output, ctf_errno (err_fp));
30517d62b00eSchristos  iterr:
30527d62b00eSchristos   ctf_err_warn (output, 0, err, _("iteration failure emitting "
30537d62b00eSchristos 				  "structure members"));
30547d62b00eSchristos   return ctf_set_errno (output, err);
30557d62b00eSchristos }
30567d62b00eSchristos 
30577d62b00eSchristos /* Emit deduplicated types into the outputs.  The shared type repository is
30587d62b00eSchristos    OUTPUT, on which the ctf_dedup function must have already been called.  The
30597d62b00eSchristos    PARENTS array contains the INPUTS index of the parent dict for every child
30607d62b00eSchristos    dict at the corresponding index in the INPUTS (for non-child dicts, the value
30617d62b00eSchristos    is undefined).
30627d62b00eSchristos 
30637d62b00eSchristos    Return an array of fps with content emitted into them (starting with OUTPUT,
30647d62b00eSchristos    which is the parent of all others, then all the newly-generated outputs).
30657d62b00eSchristos 
30667d62b00eSchristos    If CU_MAPPED is set, this is a first pass for a link with a non-empty CU
30677d62b00eSchristos    mapping: only one output will result.  */
30687d62b00eSchristos 
3069*6881a400Schristos ctf_dict_t **
3070*6881a400Schristos ctf_dedup_emit (ctf_dict_t *output, ctf_dict_t **inputs, uint32_t ninputs,
30717d62b00eSchristos 		uint32_t *parents, uint32_t *noutputs, int cu_mapped)
30727d62b00eSchristos {
30737d62b00eSchristos   size_t num_outputs = 1;		/* Always at least one output: us.  */
3074*6881a400Schristos   ctf_dict_t **outputs;
3075*6881a400Schristos   ctf_dict_t **walk;
30767d62b00eSchristos   size_t i;
30777d62b00eSchristos 
30787d62b00eSchristos   ctf_dprintf ("Triggering emission.\n");
30797d62b00eSchristos   if (ctf_dedup_walk_output_mapping (output, inputs, ninputs, parents,
30807d62b00eSchristos 				     ctf_dedup_emit_type, &cu_mapped) < 0)
30817d62b00eSchristos     return NULL;				/* errno is set for us.  */
30827d62b00eSchristos 
30837d62b00eSchristos   ctf_dprintf ("Populating struct members.\n");
30847d62b00eSchristos   if (ctf_dedup_emit_struct_members (output, inputs, ninputs, parents) < 0)
30857d62b00eSchristos     return NULL;				/* errno is set for us.  */
30867d62b00eSchristos 
30877d62b00eSchristos   for (i = 0; i < ninputs; i++)
30887d62b00eSchristos     {
30897d62b00eSchristos       if (inputs[i]->ctf_dedup.cd_output)
30907d62b00eSchristos 	num_outputs++;
30917d62b00eSchristos     }
30927d62b00eSchristos 
30937d62b00eSchristos   if (!ctf_assert (output, !cu_mapped || (cu_mapped && num_outputs == 1)))
30947d62b00eSchristos     return NULL;
30957d62b00eSchristos 
3096*6881a400Schristos   if ((outputs = calloc (num_outputs, sizeof (ctf_dict_t *))) == NULL)
30977d62b00eSchristos     {
30987d62b00eSchristos       ctf_err_warn (output, 0, ENOMEM,
30997d62b00eSchristos 		    _("out of memory allocating link outputs array"));
31007d62b00eSchristos       ctf_set_errno (output, ENOMEM);
31017d62b00eSchristos       return NULL;
31027d62b00eSchristos     }
31037d62b00eSchristos   *noutputs = num_outputs;
31047d62b00eSchristos 
31057d62b00eSchristos   walk = outputs;
31067d62b00eSchristos   *walk = output;
31077d62b00eSchristos   output->ctf_refcnt++;
31087d62b00eSchristos   walk++;
31097d62b00eSchristos 
31107d62b00eSchristos   for (i = 0; i < ninputs; i++)
31117d62b00eSchristos     {
31127d62b00eSchristos       if (inputs[i]->ctf_dedup.cd_output)
31137d62b00eSchristos 	{
31147d62b00eSchristos 	  *walk = inputs[i]->ctf_dedup.cd_output;
31157d62b00eSchristos 	  inputs[i]->ctf_dedup.cd_output = NULL;
31167d62b00eSchristos 	  walk++;
31177d62b00eSchristos 	}
31187d62b00eSchristos     }
31197d62b00eSchristos 
31207d62b00eSchristos   return outputs;
31217d62b00eSchristos }
3122*6881a400Schristos 
3123*6881a400Schristos /* Determine what type SRC_FP / SRC_TYPE was emitted as in the FP, which
3124*6881a400Schristos    must be the shared dict or have it as a parent: return 0 if none.  The SRC_FP
3125*6881a400Schristos    must be a past input to ctf_dedup.  */
3126*6881a400Schristos 
3127*6881a400Schristos ctf_id_t
3128*6881a400Schristos ctf_dedup_type_mapping (ctf_dict_t *fp, ctf_dict_t *src_fp, ctf_id_t src_type)
3129*6881a400Schristos {
3130*6881a400Schristos   ctf_dict_t *output = NULL;
3131*6881a400Schristos   ctf_dedup_t *d;
3132*6881a400Schristos   int input_num;
3133*6881a400Schristos   void *num_ptr;
3134*6881a400Schristos   void *type_ptr;
3135*6881a400Schristos   int found;
3136*6881a400Schristos   const char *hval;
3137*6881a400Schristos 
3138*6881a400Schristos   /* It is an error (an internal error in the caller, in ctf-link.c) to call
3139*6881a400Schristos      this with an FP that is not a per-CU output or shared output dict, or with
3140*6881a400Schristos      a SRC_FP that was not passed to ctf_dedup as an input; it is an internal
3141*6881a400Schristos      error in ctf-dedup for the type passed not to have been hashed, though if
3142*6881a400Schristos      the src_fp is a child dict and the type is not a child type, it will have
3143*6881a400Schristos      been hashed under the GID corresponding to the parent.  */
3144*6881a400Schristos 
3145*6881a400Schristos   if (fp->ctf_dedup.cd_type_hashes != NULL)
3146*6881a400Schristos     output = fp;
3147*6881a400Schristos   else if (fp->ctf_parent && fp->ctf_parent->ctf_dedup.cd_type_hashes != NULL)
3148*6881a400Schristos     output = fp->ctf_parent;
3149*6881a400Schristos   else
3150*6881a400Schristos     {
3151*6881a400Schristos       ctf_set_errno (fp, ECTF_INTERNAL);
3152*6881a400Schristos       ctf_err_warn (fp, 0, ECTF_INTERNAL,
3153*6881a400Schristos 		    _("dict %p passed to ctf_dedup_type_mapping is not a "
3154*6881a400Schristos 		      "deduplicated output"), (void *) fp);
3155*6881a400Schristos       return CTF_ERR;
3156*6881a400Schristos     }
3157*6881a400Schristos 
3158*6881a400Schristos   if (src_fp->ctf_parent && ctf_type_isparent (src_fp, src_type))
3159*6881a400Schristos     src_fp = src_fp->ctf_parent;
3160*6881a400Schristos 
3161*6881a400Schristos   d = &output->ctf_dedup;
3162*6881a400Schristos 
3163*6881a400Schristos   found = ctf_dynhash_lookup_kv (d->cd_input_nums, src_fp, NULL, &num_ptr);
3164*6881a400Schristos   if (!ctf_assert (output, found != 0))
3165*6881a400Schristos     return CTF_ERR;				/* errno is set for us.  */
3166*6881a400Schristos   input_num = (uintptr_t) num_ptr;
3167*6881a400Schristos 
3168*6881a400Schristos   hval = ctf_dynhash_lookup (d->cd_type_hashes,
3169*6881a400Schristos 			     CTF_DEDUP_GID (output, input_num, src_type));
3170*6881a400Schristos 
3171*6881a400Schristos   if (!ctf_assert (output, hval != NULL))
3172*6881a400Schristos     return CTF_ERR;				/* errno is set for us.  */
3173*6881a400Schristos 
3174*6881a400Schristos   /* The emission hashes may be unset if this dict was created after
3175*6881a400Schristos      deduplication to house variables or other things that would conflict if
3176*6881a400Schristos      stored in the shared dict.  */
3177*6881a400Schristos   if (fp->ctf_dedup.cd_output_emission_hashes)
3178*6881a400Schristos     if (ctf_dynhash_lookup_kv (fp->ctf_dedup.cd_output_emission_hashes, hval,
3179*6881a400Schristos 			       NULL, &type_ptr))
3180*6881a400Schristos       return (ctf_id_t) (uintptr_t) type_ptr;
3181*6881a400Schristos 
3182*6881a400Schristos   if (fp->ctf_parent)
3183*6881a400Schristos     {
3184*6881a400Schristos       ctf_dict_t *pfp = fp->ctf_parent;
3185*6881a400Schristos       if (pfp->ctf_dedup.cd_output_emission_hashes)
3186*6881a400Schristos 	if (ctf_dynhash_lookup_kv (pfp->ctf_dedup.cd_output_emission_hashes,
3187*6881a400Schristos 				   hval, NULL, &type_ptr))
3188*6881a400Schristos 	  return (ctf_id_t) (uintptr_t) type_ptr;
3189*6881a400Schristos     }
3190*6881a400Schristos 
3191*6881a400Schristos   return 0;
3192*6881a400Schristos }
3193