1/* CTF type deduplication.
2   Copyright (C) 2019 Free Software Foundation, Inc.
3
4   This file is part of libctf.
5
6   libctf is free software; you can redistribute it and/or modify it under
7   the terms of the GNU General Public License as published by the Free
8   Software Foundation; either version 3, or (at your option) any later
9   version.
10
11   This program is distributed in the hope that it will be useful, but
12   WITHOUT ANY WARRANTY; without even the implied warranty of
13   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
14   See the GNU General Public License for more details.
15
16   You should have received a copy of the GNU General Public License
17   along with this program; see the file COPYING.  If not see
18   <http://www.gnu.org/licenses/>.  */
19
20#include <ctf-impl.h>
21#include <string.h>
22#include <errno.h>
23#include <assert.h>
24#include "hashtab.h"
25
26/* (In the below, relevant functions are named in square brackets.)  */
27
28/* Type deduplication is a three-phase process:
29
30    [ctf_dedup, ctf_dedup_hash_type, ctf_dedup_rhash_type]
31    1) come up with unambiguous hash values for all types: no two types may have
32       the same hash value, and any given type should have only one hash value
33       (for optimal deduplication).
34
35    [ctf_dedup, ctf_dedup_detect_name_ambiguity,
36     ctf_dedup_conflictify_unshared, ctf_dedup_mark_conflicting_hash]
37    2) mark those distinct types with names that collide (and thus cannot be
38       declared simultaneously in the same translation unit) as conflicting, and
39       recursively mark all types that cite one of those types as conflicting as
40       well.  Possibly mark all types cited in only one TU as conflicting, if
41       the CTF_LINK_SHARE_DUPLICATED link mode is active.
42
43    [ctf_dedup_emit, ctf_dedup_emit_struct_members, ctf_dedup_id_to_target]
44    3) emit all the types, one hash value at a time.  Types not marked
45       conflicting are emitted once, into the shared dictionary: types marked
46       conflicting are emitted once per TU into a dictionary corresponding to
47       each TU in which they appear.  Structs marked conflicting get at the very
48       least a forward emitted into the shared dict so that other dicts can cite
49       it if needed.
50
51   [id_to_packed_id]
52   This all works over an array of inputs (usually in the same order as the
53   inputs on the link line).  We don't use the ctf_link_inputs hash directly
54   because it is convenient to be able to address specific input types as a
55   *global type ID* or 'GID', a pair of an array offset and a ctf_id_t.  Since
56   both are already 32 bits or less or can easily be constrained to that range,
57   we can pack them both into a single 64-bit hash word for easy lookups, which
58   would be much more annoying to do with a ctf_file_t * and a ctf_id_t.  (On
59   32-bit platforms, we must do that anyway, since pointers, and thus hash keys
60   and values, are only 32 bits wide).  We track which inputs are parents of
61   which other inputs so that we can correctly recognize that types we have
62   traversed in children may cite types in parents, and so that we can process
63   the parents first.)
64
65   Note that thanks to ld -r, the deduplicator can be fed its own output, so the
66   inputs may themselves have child dicts.  Since we need to support this usage
67   anyway, we can use it in one other place.  If the caller finds translation
68   units to be too small a unit ambiguous types, links can be 'cu-mapped', where
69   the caller provides a mapping of input TU names to output child dict names.
70   This mapping can fuse many child TUs into one potential child dict, so that
71   ambiguous types in any of those input TUs go into the same child dict.
72   When a many:1 cu-mapping is detected, the ctf_dedup machinery is called
73   repeatedly, once for every output name that has more than one input, to fuse
74   all the input TUs associated with a given output dict into one, and once again
75   as normal to deduplicate all those intermediate outputs (and any 1:1 inputs)
76   together.  This has much higher memory usage than otherwise, because in the
77   intermediate state, all the output TUs are in memory at once and cannot be
78   lazily opened.  It also has implications for the emission code: if types
79   appear ambiguously in multiple input TUs that are all mapped to the same
80   child dict, we cannot put them in children in the cu-mapping link phase
81   because this output is meant to *become* a child in the next link stage and
82   parent/child relationships are only one level deep: so instead, we just hide
83   all but one of the ambiguous types.
84
85   There are a few other subtleties here that make this more complex than it
86   seems.  Let's go over the steps above in more detail.
87
88   1) HASHING.
89
90   [ctf_dedup_hash_type, ctf_dedup_rhash_type]
91   Hashing proceeds recursively, mixing in the properties of each input type
92   (including its name, if any), and then adding the hash values of every type
93   cited by that type.  The result is stashed in the cd_type_hashes so other
94   phases can find the hash values of input types given their IDs, and so that
95   if we encounter this type again while hashing we can just return its hash
96   value: it is also stashed in the *output mapping*, a mapping from hash value
97   to the set of GIDs corresponding to that type in all inputs.  We also keep
98   track of the GID of the first appearance of the type in any input (in
99   cd_output_first_gid), and the GID of structs, unions, and forwards that only
100   appear in one TU (in cd_struct_origin).  See below for where these things are
101   used.
102
103   Everything in this phase is time-critical, because it is operating over
104   non-deduplicated types and so may have hundreds or thousands of times the
105   data volume to deal with than later phases.  Trace output is hidden behind
106   ENABLE_LIBCTF_HASH_DEBUGGING to prevent the sheer number of calls to
107   ctf_dprintf from slowing things down (tenfold slowdowns are observed purely
108   from the calls to ctf_dprintf(), even with debugging switched off), and keep
109   down the volume of output (hundreds of gigabytes of debug output are not
110   uncommon on larger links).
111
112   We have to do *something* about potential cycles in the type graph.  We'd
113   like to avoid emitting forwards in the final output if possible, because
114   forwards aren't much use: they have no members.  We are mostly saved from
115   needing to worry about this at emission time by ctf_add_struct*()
116   automatically replacing newly-created forwards when the real struct/union
117   comes along.  So we only have to avoid getting stuck in cycles during the
118   hashing phase, while also not confusing types that cite members that are
119   structs with each other.  It is easiest to solve this problem by noting two
120   things:
121
122    - all cycles in C depend on the presence of tagged structs/unions
123    - all tagged structs/unions have a unique name they can be disambiguated by
124
125   [ctf_dedup_is_stub]
126   This means that we can break all cycles by ceasing to hash in cited types at
127   every tagged struct/union and instead hashing in a stub consisting of the
128   struct/union's *decorated name*, which is the name preceded by "s " or "u "
129   depending on the namespace (cached in cd_decorated_names).  Forwards are
130   decorated identically (so a forward to "struct foo" would be represented as
131   "s foo"): this means that a citation of a forward to a type and a citation of
132   a concrete definition of a type with the same name ends up getting the same
133   hash value.
134
135   Of course, it is quite possible to have two TUs with structs with the same
136   name and different definitions, but that's OK because when we scan for types
137   with ambiguous names we will identify these and mark them conflicting.
138
139   We populate one thing to help conflictedness marking.  No unconflicted type
140   may cite a conflicted one, but this means that conflictedness marking must
141   walk from types to the types that cite them, which is the opposite of the
142   usual order.  We can make this easier to do by constructing a *citers* graph
143   in cd_citers, which points from types to the types that cite them: because we
144   emit forwards corresponding to every conflicted struct/union, we don't need
145   to do this for citations of structs/unions by other types.  This is very
146   convenient for us, because that's the only type we don't traverse
147   recursively: so we can construct the citers graph at the same time as we
148   hash, rather than needing to add an extra pass.  (This graph is a dynhash of
149   *type hash values*, so it's small: in effect it is automatically
150   deduplicated.)
151
152   2) COLLISIONAL MARKING.
153
154   [ctf_dedup_detect_name_ambiguity, ctf_dedup_mark_conflicting_hash]
155   We identify types whose names collide during the hashing process, and count
156   the rough number of uses of each name (caching may throw it off a bit: this
157   doesn't need to be accurate).  We then mark the less-frequently-cited types
158   with each names conflicting: the most-frequently-cited one goes into the
159   shared type dictionary, while all others are duplicated into per-TU
160   dictionaries, named after the input TU, that have the shared dictionary as a
161   parent.  For structures and unions this is not quite good enough: we'd like
162   to have citations of forwards to ambiguously named structures and unions
163   *stay* as citations of forwards, so that the user can tell that the caller
164   didn't actually know which structure definition was meant: but if we put one
165   of those structures into the shared dictionary, it would supplant and replace
166   the forward, leaving no sign.  So structures and unions do not take part in
167   this popularity contest: if their names are ambiguous, they are just
168   duplicated, and only a forward appears in the shared dict.
169
170   [ctf_dedup_propagate_conflictedness]
171   The process of marking types conflicted is itself recursive: we recursively
172   traverse the cd_citers graph populated in the hashing pass above and mark
173   everything that we encounter conflicted (without wasting time re-marking
174   anything that is already marked).  This naturally terminates just where we
175   want it to (at types that are cited by no other types, and at structures and
176   unions) and suffices to ensure that types that cite conflicted types are
177   always marked conflicted.
178
179   [ctf_dedup_conflictify_unshared, ctf_dedup_multiple_input_dicts]
180   When linking in CTF_LINK_SHARE_DUPLICATED mode, we would like all types that
181   are used in only one TU to end up in a per-CU dict. The easiest way to do
182   that is to mark them conflicted.  ctf_dedup_conflictify_unshared does this,
183   traversing the output mapping and using ctf_dedup_multiple_input_dicts to
184   check the number of input dicts each distinct type hash value came from:
185   types that only came from one get marked conflicted.  One caveat here is that
186   we need to consider both structs and forwards to them: a struct that appears
187   in one TU and has a dozen citations to an opaque forward in other TUs should
188   *not* be considered to be used in only one TU, because users would find it
189   useful to be able to traverse into opaque structures of that sort: so we use
190   cd_struct_origin to check both structs/unions and the forwards corresponding
191   to them.
192
193   3) EMISSION.
194
195   [ctf_dedup_walk_output_mapping, ctf_dedup_rwalk_output_mapping,
196    ctf_dedup_rwalk_one_output_mapping]
197   Emission involves another walk of the entire output mapping, this time
198   traversing everything other than struct members, recursively.  Types are
199   emitted from leaves to trunk, emitting all types a type cites before emitting
200   the type itself.  We sort the output mapping before traversing it, for
201   reproducibility and also correctness: the input dicts may have parent/child
202   relationships, so we simply sort all types that first appear in parents
203   before all children, then sort types that first appear in dicts appearing
204   earlier on the linker command line before those that appear later, then sort
205   by input ctf_id_t.  (This is where we use cd_output_first_gid, collected
206   above.)
207
208   The walking is done using a recursive traverser which arranges to not revisit
209   any type already visited and to call its callback once per input GID for
210   input GIDs corresponding to conflicted output types.  The traverser only
211   finds input types and calls a callback for them as many times as the output
212   needs to appear: it doesn't try to figure out anything about where the output
213   might go.  That's done by the callback based on whether the type is
214   marked conflicted or not.
215
216   [ctf_dedup_emit_type, ctf_dedup_id_to_target, ctf_dedup_synthesize_forward]
217   ctf_dedup_emit_type is the (sole) callback for ctf_dedup_walk_output_mapping.
218   Conflicted types have all necessary dictionaries created, and then we emit
219   the type into each dictionary in turn, working over each input CTF type
220   corresponding to each hash value and using ctf_dedup_id_to_target to map each
221   input ctf_id_t into the corresponding type in the output (dealing with input
222   ctf_id_t's with parents in the process by simply chasing to the parent dict
223   if the type we're looking up is in there).  Emitting structures involves
224   simply noting that the members of this structure need emission later on:
225   because you cannot cite a single structure member from another type, we avoid
226   emitting the members at this stage to keep recursion depths down a bit.
227
228   At this point, if we have by some mischance decided that two different types
229   with child types that hash to different values have in fact got the same hash
230   value themselves and *not* marked it conflicting, the type walk will walk
231   only *one* of them and in all likelihood we'll find that we are trying to
232   emit a type into some child dictionary that references a type that was never
233   emitted into that dictionary and assertion-fail.  This always indicates a bug
234   in the conflictedness marking machinery or the hashing code, or both.
235
236   ctf_dedup_id_to_target calls ctf_dedup_synthesize_forward to do one extra
237   thing, alluded to above: if this is a conflicted tagged structure or union,
238   and the target is the shared dict (i.e., the type we're being asked to emit
239   is not itself conflicted so can't just point straight at the conflicted
240   type), we instead synthesise a forward with the same name, emit it into the
241   shared dict, record it in cd_output_emission_conflicted_forwards so that we
242   don't re-emit it, and return it.  This means that cycles that contain
243   conflicts do not cause the entire cycle to be replicated in every child: only
244   that piece of the cycle which takes you back as far as the closest tagged
245   struct/union needs to be replicated.  This trick means that no part of the
246   deduplicator needs a cycle detector: every recursive walk can stop at tagged
247   structures.
248
249   [ctf_dedup_emit_struct_members]
250   The final stage of emission is to walk over all structures with members
251   that need emission and emit all of them. Every type has been emitted at
252   this stage, so emission cannot fail.
253
254   [ctf_dedup_populate_type_mappings, ctf_dedup_populate_type_mapping]
255   Finally, we update the input -> output type ID mappings used by the ctf-link
256   machinery to update all the other sections.  This is surprisingly expensive
257   and may be replaced with a scheme which lets the ctf-link machinery extract
258   the needed info directly from the deduplicator.  */
259
260/* Possible future optimizations are flagged with 'optimization opportunity'
261   below.  */
262
263/* Global optimization opportunity: a GC pass, eliminating types with no direct
264   or indirect citations from the other sections in the dictionary.  */
265
266/* Internal flag values for ctf_dedup_hash_type.  */
267
268/* Child call: consider forwardable types equivalent to forwards or stubs below
269   this point.  */
270#define CTF_DEDUP_HASH_INTERNAL_CHILD         0x01
271
272/* Transform references to single ctf_id_ts in passed-in inputs into a number
273   that will fit in a uint64_t.  Needs rethinking if CTF_MAX_TYPE is boosted.
274
275   On 32-bit platforms, we pack things together differently: see the note
276   above.  */
277
278#if UINTPTR_MAX < UINT64_MAX
279# define IDS_NEED_ALLOCATION 1
280# define CTF_DEDUP_GID(fp, input, type) id_to_packed_id (fp, input, type)
281# define CTF_DEDUP_GID_TO_INPUT(id) packed_id_to_input (id)
282# define CTF_DEDUP_GID_TO_TYPE(id) packed_id_to_type (id)
283#else
284# define CTF_DEDUP_GID(fp, input, type)	\
285  (void *) (((uint64_t) input) << 32 | (type))
286# define CTF_DEDUP_GID_TO_INPUT(id) ((int) (((uint64_t) id) >> 32))
287# define CTF_DEDUP_GID_TO_TYPE(id) (ctf_id_t) (((uint64_t) id) & ~(0xffffffff00000000ULL))
288#endif
289
290#ifdef IDS_NEED_ALLOCATION
291
292 /* This is the 32-bit path, which stores GIDs in a pool and returns a pointer
293    into the pool.  It is notably less efficient than the 64-bit direct storage
294    approach, but with a smaller key, this is all we can do.  */
295
296static void *
297id_to_packed_id (ctf_file_t *fp, int input_num, ctf_id_t type)
298{
299  const void *lookup;
300  ctf_type_id_key_t *dynkey = NULL;
301  ctf_type_id_key_t key = { input_num, type };
302
303  if (!ctf_dynhash_lookup_kv (fp->ctf_dedup.cd_id_to_file_t,
304			      &key, &lookup, NULL))
305    {
306      if ((dynkey = malloc (sizeof (ctf_type_id_key_t))) == NULL)
307	goto oom;
308      memcpy (dynkey, &key, sizeof (ctf_type_id_key_t));
309
310      if (ctf_dynhash_insert (fp->ctf_dedup.cd_id_to_file_t, dynkey, NULL) < 0)
311	goto oom;
312
313      ctf_dynhash_lookup_kv (fp->ctf_dedup.cd_id_to_file_t,
314			     dynkey, &lookup, NULL);
315    }
316  /* We use a raw assert() here because there isn't really a way to get any sort
317     of error back from this routine without vastly complicating things for the
318     much more common case of !IDS_NEED_ALLOCATION.  */
319  assert (lookup);
320  return (void *) lookup;
321
322 oom:
323  free (dynkey);
324  ctf_set_errno (fp, ENOMEM);
325  return NULL;
326}
327
328static int
329packed_id_to_input (const void *id)
330{
331  const ctf_type_id_key_t *key = (ctf_type_id_key_t *) id;
332
333  return key->ctii_input_num;
334}
335
336static ctf_id_t
337packed_id_to_type (const void *id)
338{
339  const ctf_type_id_key_t *key = (ctf_type_id_key_t *) id;
340
341  return key->ctii_type;
342}
343#endif
344
345/* Make an element in a dynhash-of-dynsets, or return it if already present.  */
346
347static ctf_dynset_t *
348make_set_element (ctf_dynhash_t *set, const void *key)
349{
350  ctf_dynset_t *element;
351
352  if ((element = ctf_dynhash_lookup (set, key)) == NULL)
353    {
354      if ((element = ctf_dynset_create (htab_hash_string,
355					ctf_dynset_eq_string,
356					NULL)) == NULL)
357	return NULL;
358
359      if (ctf_dynhash_insert (set, (void *) key, element) < 0)
360	{
361	  ctf_dynset_destroy (element);
362	  return NULL;
363	}
364    }
365
366  return element;
367}
368
369/* Initialize the dedup atoms table.  */
370int
371ctf_dedup_atoms_init (ctf_file_t *fp)
372{
373  if (fp->ctf_dedup_atoms)
374    return 0;
375
376  if (!fp->ctf_dedup_atoms_alloc)
377    {
378      if ((fp->ctf_dedup_atoms_alloc
379	   = ctf_dynset_create (htab_hash_string, ctf_dynset_eq_string,
380				free)) == NULL)
381	return ctf_set_errno (fp, ENOMEM);
382    }
383  fp->ctf_dedup_atoms = fp->ctf_dedup_atoms_alloc;
384  return 0;
385}
386
387/* Intern things in the dedup atoms table.  */
388
389static const char *
390intern (ctf_file_t *fp, char *atom)
391{
392  const void *foo;
393
394  if (atom == NULL)
395    return NULL;
396
397  if (!ctf_dynset_exists (fp->ctf_dedup_atoms, atom, &foo))
398    {
399      if (ctf_dynset_insert (fp->ctf_dedup_atoms, atom) < 0)
400	{
401	  ctf_set_errno (fp, ENOMEM);
402	  return NULL;
403	}
404      foo = atom;
405    }
406  else
407    free (atom);
408
409  return (const char *) foo;
410}
411
412/* Add an indication of the namespace to a type name in a way that is not valid
413   for C identifiers.  Used to maintain hashes of type names to other things
414   while allowing for the four C namespaces (normal, struct, union, enum).
415   Return a new dynamically-allocated string.  */
416static const char *
417ctf_decorate_type_name (ctf_file_t *fp, const char *name, int kind)
418{
419  ctf_dedup_t *d = &fp->ctf_dedup;
420  const char *ret;
421  const char *k;
422  char *p;
423  size_t i;
424
425  switch (kind)
426    {
427    case CTF_K_STRUCT:
428      k = "s ";
429      i = 0;
430      break;
431    case CTF_K_UNION:
432      k = "u ";
433      i = 1;
434      break;
435    case CTF_K_ENUM:
436      k = "e ";
437      i = 2;
438      break;
439    default:
440      k = "";
441      i = 3;
442    }
443
444  if ((ret = ctf_dynhash_lookup (d->cd_decorated_names[i], name)) == NULL)
445    {
446      char *str;
447
448      if ((str = malloc (strlen (name) + strlen (k) + 1)) == NULL)
449	goto oom;
450
451      p = stpcpy (str, k);
452      strcpy (p, name);
453      ret = intern (fp, str);
454      if (!ret)
455	goto oom;
456
457      if (ctf_dynhash_cinsert (d->cd_decorated_names[i], name, ret) < 0)
458	goto oom;
459    }
460
461  return ret;
462
463 oom:
464  ctf_set_errno (fp, ENOMEM);
465  return NULL;
466}
467
468/* Hash a type, possibly debugging-dumping something about it as well.  */
469static inline void
470ctf_dedup_sha1_add (ctf_sha1_t *sha1, const void *buf, size_t len,
471		    const char *description _libctf_unused_,
472		    unsigned long depth _libctf_unused_)
473{
474  ctf_sha1_add (sha1, buf, len);
475
476#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
477  ctf_sha1_t tmp;
478  char tmp_hval[CTF_SHA1_SIZE];
479  tmp = *sha1;
480  ctf_sha1_fini (&tmp, tmp_hval);
481  ctf_dprintf ("%lu: after hash addition of %s: %s\n", depth, description,
482	       tmp_hval);
483#endif
484}
485
486static const char *
487ctf_dedup_hash_type (ctf_file_t *fp, ctf_file_t *input,
488		     ctf_file_t **inputs, uint32_t *parents,
489		     int input_num, ctf_id_t type, int flags,
490		     unsigned long depth,
491		     int (*populate_fun) (ctf_file_t *fp,
492					  ctf_file_t *input,
493					  ctf_file_t **inputs,
494					  int input_num,
495					  ctf_id_t type,
496					  void *id,
497					  const char *decorated_name,
498					  const char *hash));
499
500/* Determine whether this type is being hashed as a stub (in which case it is
501   unsafe to cache it).  */
502static int
503ctf_dedup_is_stub (const char *name, int kind, int fwdkind, int flags)
504{
505  /* We can cache all types unless we are recursing to children and are hashing
506     in a tagged struct, union or forward, all of which are replaced with their
507     decorated name as a stub and will have different hash values when hashed at
508     the top level.  */
509
510  return ((flags & CTF_DEDUP_HASH_INTERNAL_CHILD) && name
511	  && (kind == CTF_K_STRUCT || kind == CTF_K_UNION
512	      || (kind == CTF_K_FORWARD && (fwdkind == CTF_K_STRUCT
513					    || fwdkind == CTF_K_UNION))));
514}
515
516/* Populate struct_origin if need be (not already populated, or populated with
517   a different origin), in which case it must go to -1, "shared".)
518
519   Only called for forwards or forwardable types with names, when the link mode
520   is CTF_LINK_SHARE_DUPLICATED.  */
521static int
522ctf_dedup_record_origin (ctf_file_t *fp, int input_num, const char *decorated,
523			 void *id)
524{
525  ctf_dedup_t *d = &fp->ctf_dedup;
526  void *origin;
527  int populate_origin = 0;
528
529  if (ctf_dynhash_lookup_kv (d->cd_struct_origin, decorated, NULL, &origin))
530    {
531      if (CTF_DEDUP_GID_TO_INPUT (origin) != input_num
532	  && CTF_DEDUP_GID_TO_INPUT (origin) != -1)
533	{
534	  populate_origin = 1;
535	  origin = CTF_DEDUP_GID (fp, -1, -1);
536	}
537    }
538  else
539    {
540      populate_origin = 1;
541      origin = id;
542    }
543
544  if (populate_origin)
545    if (ctf_dynhash_cinsert (d->cd_struct_origin, decorated, origin) < 0)
546      return ctf_set_errno (fp, errno);
547  return 0;
548}
549
550/* Do the underlying hashing and recursion for ctf_dedup_hash_type (which it
551   calls, recursively).  */
552
553static const char *
554ctf_dedup_rhash_type (ctf_file_t *fp, ctf_file_t *input, ctf_file_t **inputs,
555		      uint32_t *parents, int input_num, ctf_id_t type,
556		      void *type_id, const ctf_type_t *tp, const char *name,
557		      const char *decorated, int kind, int flags,
558		      unsigned long depth,
559		      int (*populate_fun) (ctf_file_t *fp,
560					   ctf_file_t *input,
561					   ctf_file_t **inputs,
562					   int input_num,
563					   ctf_id_t type,
564					   void *id,
565					   const char *decorated_name,
566					   const char *hash))
567{
568  ctf_dedup_t *d = &fp->ctf_dedup;
569  ctf_next_t *i = NULL;
570  ctf_sha1_t hash;
571  ctf_id_t child_type;
572  char hashbuf[CTF_SHA1_SIZE];
573  const char *hval = NULL;
574  const char *whaterr;
575  int err;
576
577  const char *citer = NULL;
578  ctf_dynset_t *citers = NULL;
579
580  /* Add a citer to the citers set.  */
581#define ADD_CITER(citers, hval)						\
582  do									\
583    {									\
584      whaterr = N_("error updating citers");				\
585      if (!citers)							\
586	if ((citers = ctf_dynset_create (htab_hash_string,		\
587					  ctf_dynset_eq_string,		\
588					  NULL)) == NULL)		\
589	  goto oom;							\
590      if (ctf_dynset_cinsert (citers, hval) < 0)			\
591	goto oom;							\
592    } while (0)
593
594  /* If this is a named struct or union or a forward to one, and this is a child
595     traversal, treat this type as if it were a forward -- do not recurse to
596     children, ignore all content not already hashed in, and hash in the
597     decorated name of the type instead.  */
598
599  if (ctf_dedup_is_stub (name, kind, tp->ctt_type, flags))
600    {
601#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
602      ctf_dprintf ("Struct/union/forward citation: substituting forwarding "
603		   "stub with decorated name %s\n", decorated);
604
605#endif
606      ctf_sha1_init (&hash);
607      ctf_dedup_sha1_add (&hash, decorated, strlen (decorated) + 1,
608			  "decorated struct/union/forward name", depth);
609      ctf_sha1_fini (&hash, hashbuf);
610
611      if ((hval = intern (fp, strdup (hashbuf))) == NULL)
612	{
613	  ctf_err_warn (fp, 0, 0, _("%s (%i): out of memory during forwarding-"
614				    "stub hashing for type with GID %p"),
615			ctf_link_input_name (input), input_num, type_id);
616	  return NULL;				/* errno is set for us.  */
617	}
618
619      /* In share-duplicated link mode, make sure the origin of this type is
620	 recorded, even if this is a type in a parent dict which will not be
621	 directly traversed.  */
622      if (d->cd_link_flags & CTF_LINK_SHARE_DUPLICATED
623	  && ctf_dedup_record_origin (fp, input_num, decorated, type_id) < 0)
624	return NULL;				/* errno is set for us.  */
625
626      return hval;
627    }
628
629  /* Now ensure that subsequent recursive calls (but *not* the top-level call)
630     get this treatment.  */
631  flags |= CTF_DEDUP_HASH_INTERNAL_CHILD;
632
633  /* If this is a struct, union, or forward with a name, record the unique
634     originating input TU, if there is one.  */
635
636  if (decorated && (ctf_forwardable_kind (kind) || kind != CTF_K_FORWARD))
637    if (d->cd_link_flags & CTF_LINK_SHARE_DUPLICATED
638	&& ctf_dedup_record_origin (fp, input_num, decorated, type_id) < 0)
639      return NULL;				/* errno is set for us.  */
640
641  /* Mix in invariant stuff, transforming the type kind if needed.  Note that
642     the vlen is *not* hashed in: the actual variable-length info is hashed in
643     instead, piecewise.  The vlen is not part of the type, only the
644     variable-length data is: identical types with distinct vlens are quite
645     possible.  Equally, we do not want to hash in the isroot flag: both the
646     compiler and the deduplicator set the nonroot flag to indicate clashes with
647     *other types in the same TU* with the same name: so two types can easily
648     have distinct nonroot flags, yet be exactly the same type.*/
649
650#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
651  ctf_dprintf ("%lu: hashing thing with ID %i/%lx (kind %i): %s.\n",
652	       depth, input_num, type, kind, name ? name : "");
653#endif
654
655  ctf_sha1_init (&hash);
656  if (name)
657    ctf_dedup_sha1_add (&hash, name, strlen (name) + 1, "name", depth);
658  ctf_dedup_sha1_add (&hash, &kind, sizeof (uint32_t), "kind", depth);
659
660  /* Hash content of this type.  */
661  switch (kind)
662    {
663    case CTF_K_UNKNOWN:
664      /* No extra state.  */
665      break;
666    case CTF_K_FORWARD:
667
668      /* Add the forwarded kind, stored in the ctt_type.  */
669      ctf_dedup_sha1_add (&hash, &tp->ctt_type, sizeof (tp->ctt_type),
670			  "forwarded kind", depth);
671      break;
672    case CTF_K_INTEGER:
673    case CTF_K_FLOAT:
674      {
675	ctf_encoding_t ep;
676	memset (&ep, 0, sizeof (ctf_encoding_t));
677
678	ctf_dedup_sha1_add (&hash, &tp->ctt_size, sizeof (uint32_t), "size",
679			    depth);
680	if (ctf_type_encoding (input, type, &ep) < 0)
681	  {
682	    whaterr = N_("error getting encoding");
683	    goto err;
684	  }
685	ctf_dedup_sha1_add (&hash, &ep, sizeof (ctf_encoding_t), "encoding",
686			    depth);
687	break;
688      }
689      /* Types that reference other types.  */
690    case CTF_K_TYPEDEF:
691    case CTF_K_VOLATILE:
692    case CTF_K_CONST:
693    case CTF_K_RESTRICT:
694    case CTF_K_POINTER:
695      /* Hash the referenced type, if not already hashed, and mix it in.  */
696      child_type = ctf_type_reference (input, type);
697      if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents, input_num,
698				       child_type, flags, depth,
699				       populate_fun)) == NULL)
700	{
701	  whaterr = N_("error doing referenced type hashing");
702	  goto err;
703	}
704      ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "referenced type",
705			  depth);
706      citer = hval;
707
708      break;
709
710      /* The slices of two types hash identically only if the type they overlay
711	 also has the same encoding.  This is not ideal, but in practice will work
712	 well enough.  We work directly rather than using the CTF API because
713	 we do not want the slice's normal automatically-shine-through
714	 semantics to kick in here.  */
715    case CTF_K_SLICE:
716      {
717	const ctf_slice_t *slice;
718	const ctf_dtdef_t *dtd;
719	ssize_t size;
720	ssize_t increment;
721
722	child_type = ctf_type_reference (input, type);
723	ctf_get_ctt_size (input, tp, &size, &increment);
724	ctf_dedup_sha1_add (&hash, &size, sizeof (ssize_t), "size", depth);
725
726	if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents, input_num,
727					 child_type, flags, depth,
728					 populate_fun)) == NULL)
729	  {
730	    whaterr = N_("error doing slice-referenced type hashing");
731	    goto err;
732	  }
733	ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "sliced type",
734			    depth);
735	citer = hval;
736
737	if ((dtd = ctf_dynamic_type (input, type)) != NULL)
738	  slice = &dtd->dtd_u.dtu_slice;
739	else
740	  slice = (ctf_slice_t *) ((uintptr_t) tp + increment);
741
742	ctf_dedup_sha1_add (&hash, &slice->cts_offset,
743			    sizeof (slice->cts_offset), "slice offset", depth);
744	ctf_dedup_sha1_add (&hash, &slice->cts_bits,
745			    sizeof (slice->cts_bits), "slice bits", depth);
746	break;
747      }
748
749    case CTF_K_ARRAY:
750      {
751	ctf_arinfo_t ar;
752
753	if (ctf_array_info (input, type, &ar) < 0)
754	  {
755	    whaterr = N_("error getting array info");
756	    goto err;
757	  }
758
759	if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents, input_num,
760					 ar.ctr_contents, flags, depth,
761					 populate_fun)) == NULL)
762	  {
763	    whaterr = N_("error doing array contents type hashing");
764	    goto err;
765	  }
766	ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "array contents",
767			    depth);
768	ADD_CITER (citers, hval);
769
770	if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents, input_num,
771					 ar.ctr_index, flags, depth,
772					 populate_fun)) == NULL)
773	  {
774	    whaterr = N_("error doing array index type hashing");
775	    goto err;
776	  }
777	ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "array index",
778			    depth);
779	ctf_dedup_sha1_add (&hash, &ar.ctr_nelems, sizeof (ar.ctr_nelems),
780			    "element count", depth);
781	ADD_CITER (citers, hval);
782
783	break;
784      }
785    case CTF_K_FUNCTION:
786      {
787	ctf_funcinfo_t fi;
788	ctf_id_t *args;
789	uint32_t j;
790
791	if (ctf_func_type_info (input, type, &fi) < 0)
792	  {
793	    whaterr = N_("error getting func type info");
794	    goto err;
795	  }
796
797	if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents, input_num,
798					 fi.ctc_return, flags, depth,
799					 populate_fun)) == NULL)
800	  {
801	    whaterr = N_("error getting func return type");
802	    goto err;
803	  }
804	ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "func return",
805			    depth);
806	ctf_dedup_sha1_add (&hash, &fi.ctc_argc, sizeof (fi.ctc_argc),
807			    "func argc", depth);
808	ctf_dedup_sha1_add (&hash, &fi.ctc_flags, sizeof (fi.ctc_flags),
809			    "func flags", depth);
810	ADD_CITER (citers, hval);
811
812	if ((args = calloc (fi.ctc_argc, sizeof (ctf_id_t))) == NULL)
813	  {
814	    whaterr = N_("error doing memory allocation");
815	    goto err;
816	  }
817
818	if (ctf_func_type_args (input, type, fi.ctc_argc, args) < 0)
819	  {
820	    free (args);
821	    whaterr = N_("error getting func arg type");
822	    goto err;
823	  }
824	for (j = 0; j < fi.ctc_argc; j++)
825	  {
826	    if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents,
827					     input_num, args[j], flags, depth,
828					     populate_fun)) == NULL)
829	      {
830		free (args);
831		whaterr = N_("error doing func arg type hashing");
832		goto err;
833	      }
834	    ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "func arg type",
835				depth);
836	    ADD_CITER (citers, hval);
837	  }
838	free (args);
839	break;
840      }
841    case CTF_K_ENUM:
842      {
843	int val;
844	const char *ename;
845
846	ctf_dedup_sha1_add (&hash, &tp->ctt_size, sizeof (uint32_t),
847			    "enum size", depth);
848	while ((ename = ctf_enum_next (input, type, &i, &val)) != NULL)
849	  {
850	    ctf_dedup_sha1_add (&hash, ename, strlen (ename) + 1, "enumerator",
851				depth);
852	    ctf_dedup_sha1_add (&hash, &val, sizeof (val), "enumerand", depth);
853	  }
854	if (ctf_errno (input) != ECTF_NEXT_END)
855	  {
856	    whaterr = N_("error doing enum member iteration");
857	    goto err;
858	  }
859	break;
860      }
861    /* Top-level only.  */
862    case CTF_K_STRUCT:
863    case CTF_K_UNION:
864      {
865	ssize_t offset;
866	const char *mname;
867	ctf_id_t membtype;
868	ssize_t size;
869
870	ctf_get_ctt_size (input, tp, &size, NULL);
871	ctf_dedup_sha1_add (&hash, &size, sizeof (ssize_t), "struct size",
872			    depth);
873
874	while ((offset = ctf_member_next (input, type, &i, &mname,
875					  &membtype)) >= 0)
876	  {
877	    if (mname == NULL)
878	      mname = "";
879	    ctf_dedup_sha1_add (&hash, mname, strlen (mname) + 1,
880				"member name", depth);
881
882#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
883	    ctf_dprintf ("%lu: Traversing to member %s\n", depth, mname);
884#endif
885	    if ((hval = ctf_dedup_hash_type (fp, input, inputs, parents,
886					     input_num, membtype, flags, depth,
887					     populate_fun)) == NULL)
888	      {
889		whaterr = N_("error doing struct/union member type hashing");
890		goto iterr;
891	      }
892
893	    ctf_dedup_sha1_add (&hash, hval, strlen (hval) + 1, "member hash",
894				depth);
895	    ctf_dedup_sha1_add (&hash, &offset, sizeof (offset), "member offset",
896				depth);
897	    ADD_CITER (citers, hval);
898	  }
899	if (ctf_errno (input) != ECTF_NEXT_END)
900	  {
901	    whaterr = N_("error doing struct/union member iteration");
902	    goto err;
903	  }
904	break;
905      }
906    default:
907      whaterr = N_("error: unknown type kind");
908      goto err;
909    }
910  ctf_sha1_fini (&hash, hashbuf);
911
912  if ((hval = intern (fp, strdup (hashbuf))) == NULL)
913    {
914      whaterr = N_("cannot intern hash");
915      goto oom;
916    }
917
918  /* Populate the citers for this type's subtypes, now the hash for the type
919     itself is known.  */
920  whaterr = N_("error tracking citers");
921
922  if (citer)
923    {
924      ctf_dynset_t *citer_hashes;
925
926      if ((citer_hashes = make_set_element (d->cd_citers, citer)) == NULL)
927	goto oom;
928      if (ctf_dynset_cinsert (citer_hashes, hval) < 0)
929	goto oom;
930    }
931  else if (citers)
932    {
933      const void *k;
934
935      while ((err = ctf_dynset_cnext (citers, &i, &k)) == 0)
936	{
937	  ctf_dynset_t *citer_hashes;
938	  citer = (const char *) k;
939
940	  if ((citer_hashes = make_set_element (d->cd_citers, citer)) == NULL)
941	    goto oom;
942
943	  if (ctf_dynset_exists (citer_hashes, hval, NULL))
944	    continue;
945	  if (ctf_dynset_cinsert (citer_hashes, hval) < 0)
946	    goto oom;
947	}
948      if (err != ECTF_NEXT_END)
949	goto err;
950      ctf_dynset_destroy (citers);
951    }
952
953  return hval;
954
955 iterr:
956  ctf_next_destroy (i);
957 err:
958  ctf_sha1_fini (&hash, NULL);
959  ctf_err_warn (fp, 0, 0, _("%s (%i): %s: during type hashing for type %lx, "
960			    "kind %i"), ctf_link_input_name (input),
961		input_num, gettext (whaterr), type, kind);
962  return NULL;
963 oom:
964  ctf_set_errno (fp, errno);
965  ctf_err_warn (fp, 0, 0, _("%s (%i): %s: during type hashing for type %lx, "
966			    "kind %i"), ctf_link_input_name (input),
967		input_num, gettext (whaterr), type, kind);
968  return NULL;
969}
970
971/* Hash a TYPE in the INPUT: FP is the eventual output, where the ctf_dedup
972   state is stored.  INPUT_NUM is the number of this input in the set of inputs.
973   Record its hash in FP's cd_type_hashes once it is known.  PARENTS is
974   described in the comment above ctf_dedup.
975
976   (The flags argument currently accepts only the flag
977   CTF_DEDUP_HASH_INTERNAL_CHILD, an implementation detail used to prevent
978   struct/union hashing in recursive traversals below the TYPE.)
979
980   We use the CTF API rather than direct access wherever possible, because types
981   that appear identical through the API should be considered identical, with
982   one exception: slices should only be considered identical to other slices,
983   not to the corresponding unsliced type.
984
985   The POPULATE_FUN is a mandatory hook that populates other mappings with each
986   type we see (excepting types that are recursively hashed as stubs).  The
987   caller should not rely on the order of calls to this hook, though it will be
988   called at least once for every non-stub reference to every type.
989
990   Returns a hash value (an atom), or NULL on error.  */
991
992static const char *
993ctf_dedup_hash_type (ctf_file_t *fp, ctf_file_t *input,
994		     ctf_file_t **inputs, uint32_t *parents,
995		     int input_num, ctf_id_t type, int flags,
996		     unsigned long depth,
997		     int (*populate_fun) (ctf_file_t *fp,
998					  ctf_file_t *input,
999					  ctf_file_t **inputs,
1000					  int input_num,
1001					  ctf_id_t type,
1002					  void *id,
1003					  const char *decorated_name,
1004					  const char *hash))
1005{
1006  ctf_dedup_t *d = &fp->ctf_dedup;
1007  const ctf_type_t *tp;
1008  void *type_id;
1009  const char *hval = NULL;
1010  const char *name;
1011  const char *whaterr;
1012  const char *decorated = NULL;
1013  uint32_t kind, fwdkind;
1014
1015  depth++;
1016
1017#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1018  ctf_dprintf ("%lu: ctf_dedup_hash_type (%i, %lx, flags %x)\n", depth, input_num, type, flags);
1019#endif
1020
1021  /* The unimplemented type doesn't really exist, but must be noted in parent
1022     hashes: so it gets a fixed, arbitrary hash.  */
1023  if (type == 0)
1024    return "00000000000000000000";
1025
1026  /* Possible optimization: if the input type is in the parent type space, just
1027     copy recursively-cited hashes from the parent's types into the output
1028     mapping rather than rehashing them.  */
1029
1030  type_id = CTF_DEDUP_GID (fp, input_num, type);
1031
1032  if ((tp = ctf_lookup_by_id (&input, type)) == NULL)
1033    {
1034      ctf_set_errno (fp, ctf_errno (input));
1035      ctf_err_warn (fp, 0, 0, _("%s (%i): lookup failure for type %lx: "
1036				"flags %x"), ctf_link_input_name (input),
1037		    input_num, type, flags);
1038      return NULL;		/* errno is set for us.  */
1039    }
1040
1041  kind = LCTF_INFO_KIND (input, tp->ctt_info);
1042  name = ctf_strraw (input, tp->ctt_name);
1043
1044  if (tp->ctt_name == 0 || !name || name[0] == '\0')
1045    name = NULL;
1046
1047  /* Treat the unknown kind just like the unimplemented type.  */
1048  if (kind == CTF_K_UNKNOWN)
1049    return "00000000000000000000";
1050
1051  /* Decorate the name appropriately for the namespace it appears in: forwards
1052     appear in the namespace of their referent.  */
1053
1054  fwdkind = kind;
1055  if (name)
1056    {
1057      if (kind == CTF_K_FORWARD)
1058	fwdkind = tp->ctt_type;
1059
1060      if ((decorated = ctf_decorate_type_name (fp, name, fwdkind)) == NULL)
1061	return NULL;				/* errno is set for us.  */
1062    }
1063
1064  /* If not hashing a stub, we can rely on various sorts of caches.
1065
1066     Optimization opportunity: we may be able to avoid calling the populate_fun
1067     sometimes here.  */
1068
1069  if (!ctf_dedup_is_stub (name, kind, fwdkind, flags))
1070    {
1071      if ((hval = ctf_dynhash_lookup (d->cd_type_hashes, type_id)) != NULL)
1072	{
1073#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1074	  ctf_dprintf ("%lu: Known hash for ID %i/%lx: %s\n", depth, input_num,
1075		       type,  hval);
1076#endif
1077	  populate_fun (fp, input, inputs, input_num, type, type_id,
1078			decorated, hval);
1079
1080	  return hval;
1081	}
1082    }
1083
1084  /* We have never seen this type before, and must figure out its hash and the
1085     hashes of the types it cites.
1086
1087     Hash this type, and call ourselves recursively.  (The hashing part is
1088     optional, and is disabled if overidden_hval is set.)  */
1089
1090  if ((hval = ctf_dedup_rhash_type (fp, input, inputs, parents, input_num,
1091				    type, type_id, tp, name, decorated,
1092				    kind, flags, depth, populate_fun)) == NULL)
1093    return NULL;				/* errno is set for us.  */
1094
1095  /* The hash of this type is now known: record it unless caching is unsafe
1096     because the hash value will change later.  This will be the final storage
1097     of this type's hash, so we call the population function on it.  */
1098
1099  if (!ctf_dedup_is_stub (name, kind, fwdkind, flags))
1100    {
1101#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1102      ctf_dprintf ("Caching %lx, ID %p (%s), %s in final location\n", type,
1103		   type_id, name ? name : "", hval);
1104#endif
1105
1106      if (ctf_dynhash_cinsert (d->cd_type_hashes, type_id, hval) < 0)
1107	{
1108	  whaterr = N_("error hash caching");
1109	  goto oom;
1110	}
1111
1112      if (populate_fun (fp, input, inputs, input_num, type, type_id,
1113			decorated, hval) < 0)
1114	{
1115	  whaterr = N_("error calling population function");
1116	  goto err;				/* errno is set for us. */
1117	}
1118    }
1119
1120#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1121  ctf_dprintf ("%lu: Returning final hash for ID %i/%lx: %s\n", depth,
1122	       input_num, type, hval);
1123#endif
1124  return hval;
1125
1126 oom:
1127  ctf_set_errno (fp, errno);
1128 err:
1129  ctf_err_warn (fp, 0, 0, _("%s (%i): %s: during type hashing, "
1130			    "type %lx, kind %i"),
1131		ctf_link_input_name (input), input_num,
1132		gettext (whaterr), type, kind);
1133  return NULL;
1134}
1135
1136/* Populate a number of useful mappings not directly used by the hashing
1137   machinery: the output mapping, the cd_name_counts mapping from name -> hash
1138   -> count of hashval deduplication state for a given hashed type, and the
1139   cd_output_first_tu mapping.  */
1140
1141static int
1142ctf_dedup_populate_mappings (ctf_file_t *fp, ctf_file_t *input _libctf_unused_,
1143			     ctf_file_t **inputs _libctf_unused_,
1144			     int input_num _libctf_unused_,
1145			     ctf_id_t type _libctf_unused_, void *id,
1146			     const char *decorated_name,
1147			     const char *hval)
1148{
1149  ctf_dedup_t *d = &fp->ctf_dedup;
1150  ctf_dynset_t *type_ids;
1151  ctf_dynhash_t *name_counts;
1152  long int count;
1153
1154#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1155  ctf_dprintf ("Hash %s, %s, into output mapping for %i/%lx @ %s\n",
1156	       hval, decorated_name ? decorated_name : "(unnamed)",
1157	       input_num, type, ctf_link_input_name (input));
1158
1159  const char *orig_hval;
1160
1161  /* Make sure we never map a single GID to multiple hash values.  */
1162
1163  if ((orig_hval = ctf_dynhash_lookup (d->cd_output_mapping_guard, id)) != NULL)
1164    {
1165      /* We can rely on pointer identity here, since all hashes are
1166	 interned.  */
1167      if (!ctf_assert (fp, orig_hval == hval))
1168	return -1;
1169    }
1170  else
1171    if (ctf_dynhash_cinsert (d->cd_output_mapping_guard, id, hval) < 0)
1172      return ctf_set_errno (fp, errno);
1173#endif
1174
1175  /* Record the type in the output mapping: if this is the first time this type
1176     has been seen, also record it in the cd_output_first_gid.  Because we
1177     traverse types in TU order and we do not merge types after the hashing
1178     phase, this will be the lowest TU this type ever appears in.  */
1179
1180  if ((type_ids = ctf_dynhash_lookup (d->cd_output_mapping,
1181				      hval)) == NULL)
1182    {
1183      if (ctf_dynhash_cinsert (d->cd_output_first_gid, hval, id) < 0)
1184	return ctf_set_errno (fp, errno);
1185
1186      if ((type_ids = ctf_dynset_create (htab_hash_pointer,
1187					 htab_eq_pointer,
1188					 NULL)) == NULL)
1189	return ctf_set_errno (fp, errno);
1190      if (ctf_dynhash_insert (d->cd_output_mapping, (void *) hval,
1191			      type_ids) < 0)
1192	{
1193	  ctf_dynset_destroy (type_ids);
1194	  return ctf_set_errno (fp, errno);
1195	}
1196    }
1197#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1198    {
1199      /* Verify that all types with this hash are of the same kind, and that the
1200	 first TU a type was seen in never falls.  */
1201
1202      int err;
1203      const void *one_id;
1204      ctf_next_t *i = NULL;
1205      int orig_kind = ctf_type_kind_unsliced (input, type);
1206      int orig_first_tu;
1207
1208      orig_first_tu = CTF_DEDUP_GID_TO_INPUT
1209	(ctf_dynhash_lookup (d->cd_output_first_gid, hval));
1210      if (!ctf_assert (fp, orig_first_tu <= CTF_DEDUP_GID_TO_INPUT (id)))
1211	return -1;
1212
1213      while ((err = ctf_dynset_cnext (type_ids, &i, &one_id)) == 0)
1214	{
1215	  ctf_file_t *foo = inputs[CTF_DEDUP_GID_TO_INPUT (one_id)];
1216	  ctf_id_t bar = CTF_DEDUP_GID_TO_TYPE (one_id);
1217	  if (ctf_type_kind_unsliced (foo, bar) != orig_kind)
1218	    {
1219	      ctf_err_warn (fp, 1, 0, "added wrong kind to output mapping "
1220			    "for hash %s named %s: %p/%lx from %s is "
1221			    "kind %i, but newly-added %p/%lx from %s is "
1222			    "kind %i", hval,
1223			    decorated_name ? decorated_name : "(unnamed)",
1224			    (void *) foo, bar,
1225			    ctf_link_input_name (foo),
1226			    ctf_type_kind_unsliced (foo, bar),
1227			    (void *) input, type,
1228			    ctf_link_input_name (input), orig_kind);
1229	      if (!ctf_assert (fp, ctf_type_kind_unsliced (foo, bar)
1230			       == orig_kind))
1231		return -1;
1232	    }
1233	}
1234      if (err != ECTF_NEXT_END)
1235	return ctf_set_errno (fp, err);
1236    }
1237#endif
1238
1239  /* This function will be repeatedly called for the same types many times:
1240     don't waste time reinserting the same keys in that case.  */
1241  if (!ctf_dynset_exists (type_ids, id, NULL)
1242      && ctf_dynset_insert (type_ids, id) < 0)
1243    return ctf_set_errno (fp, errno);
1244
1245  /* The rest only needs to happen for types with names.  */
1246  if (!decorated_name)
1247    return 0;
1248
1249  /* Count the number of occurrences of the hash value for this GID.  */
1250
1251  hval = ctf_dynhash_lookup (d->cd_type_hashes, id);
1252
1253  /* Mapping from name -> hash(hashval, count) not already present?  */
1254  if ((name_counts = ctf_dynhash_lookup (d->cd_name_counts,
1255					 decorated_name)) == NULL)
1256    {
1257      if ((name_counts = ctf_dynhash_create (ctf_hash_string,
1258					     ctf_hash_eq_string,
1259					     NULL, NULL)) == NULL)
1260	  return ctf_set_errno (fp, errno);
1261      if (ctf_dynhash_cinsert (d->cd_name_counts, decorated_name,
1262			       name_counts) < 0)
1263	{
1264	  ctf_dynhash_destroy (name_counts);
1265	  return ctf_set_errno (fp, errno);
1266	}
1267    }
1268
1269  /* This will, conveniently, return NULL (i.e. 0) for a new entry.  */
1270  count = (long int) (uintptr_t) ctf_dynhash_lookup (name_counts, hval);
1271
1272  if (ctf_dynhash_cinsert (name_counts, hval,
1273			   (const void *) (uintptr_t) (count + 1)) < 0)
1274    return ctf_set_errno (fp, errno);
1275
1276  return 0;
1277}
1278
1279/* Mark a single hash as corresponding to a conflicting type.  Mark all types
1280   that cite it as conflicting as well, terminating the recursive walk only when
1281   types that are already conflicted or types do not cite other types are seen.
1282   (Tagged structures and unions do not appear in the cd_citers graph, so the
1283   walk also terminates there, since any reference to a conflicting structure is
1284   just going to reference an unconflicting forward instead: see
1285   ctf_dedup_maybe_synthesize_forward.)  */
1286
1287static int
1288ctf_dedup_mark_conflicting_hash (ctf_file_t *fp, const char *hval)
1289{
1290  ctf_dedup_t *d = &fp->ctf_dedup;
1291  ctf_next_t *i = NULL;
1292  int err;
1293  const void *k;
1294  ctf_dynset_t *citers;
1295
1296  /* Mark conflicted if not already so marked.  */
1297  if (ctf_dynset_exists (d->cd_conflicting_types, hval, NULL))
1298    return 0;
1299
1300  ctf_dprintf ("Marking %s as conflicted\n", hval);
1301
1302  if (ctf_dynset_cinsert (d->cd_conflicting_types, hval) < 0)
1303    {
1304      ctf_dprintf ("Out of memory marking %s as conflicted\n", hval);
1305      ctf_set_errno (fp, errno);
1306      return -1;
1307    }
1308
1309  /* If any types cite this type, mark them conflicted too.  */
1310  if ((citers = ctf_dynhash_lookup (d->cd_citers, hval)) == NULL)
1311    return 0;
1312
1313  while ((err = ctf_dynset_cnext (citers, &i, &k)) == 0)
1314    {
1315      const char *hv = (const char *) k;
1316
1317      if (ctf_dynset_exists (d->cd_conflicting_types, hv, NULL))
1318	continue;
1319
1320      if (ctf_dedup_mark_conflicting_hash (fp, hv) < 0)
1321	{
1322	  ctf_next_destroy (i);
1323	  return -1;				/* errno is set for us.  */
1324	}
1325    }
1326  if (err != ECTF_NEXT_END)
1327    return ctf_set_errno (fp, err);
1328
1329  return 0;
1330}
1331
1332/* Look up a type kind from the output mapping, given a type hash value.  */
1333static int
1334ctf_dedup_hash_kind (ctf_file_t *fp, ctf_file_t **inputs, const char *hash)
1335{
1336  ctf_dedup_t *d = &fp->ctf_dedup;
1337  void *id;
1338  ctf_dynset_t *type_ids;
1339
1340  /* Precondition: the output mapping is populated.  */
1341  if (!ctf_assert (fp, ctf_dynhash_elements (d->cd_output_mapping) > 0))
1342    return -1;
1343
1344  /* Look up some GID from the output hash for this type.  (They are all
1345     identical, so we can pick any).  Don't assert if someone calls this
1346     function wrongly, but do assert if the output mapping knows about the hash,
1347     but has nothing associated with it.  */
1348
1349  type_ids = ctf_dynhash_lookup (d->cd_output_mapping, hash);
1350  if (!type_ids)
1351    {
1352      ctf_dprintf ("Looked up type kind by nonexistent hash %s.\n", hash);
1353      return ctf_set_errno (fp, ECTF_INTERNAL);
1354    }
1355  id = ctf_dynset_lookup_any (type_ids);
1356  if (!ctf_assert (fp, id))
1357    return -1;
1358
1359  return ctf_type_kind_unsliced (inputs[CTF_DEDUP_GID_TO_INPUT (id)],
1360				 CTF_DEDUP_GID_TO_TYPE (id));
1361}
1362
1363/* Used to keep a count of types: i.e. distinct type hash values.  */
1364typedef struct ctf_dedup_type_counter
1365{
1366  ctf_file_t *fp;
1367  ctf_file_t **inputs;
1368  int num_non_forwards;
1369} ctf_dedup_type_counter_t;
1370
1371/* Add to the type counter for one name entry from the cd_name_counts.  */
1372static int
1373ctf_dedup_count_types (void *key_, void *value _libctf_unused_, void *arg_)
1374{
1375  const char *hval = (const char *) key_;
1376  int kind;
1377  ctf_dedup_type_counter_t *arg = (ctf_dedup_type_counter_t *) arg_;
1378
1379  kind = ctf_dedup_hash_kind (arg->fp, arg->inputs, hval);
1380
1381  /* We rely on ctf_dedup_hash_kind setting the fp to -ECTF_INTERNAL on error to
1382     smuggle errors out of here.  */
1383
1384  if (kind != CTF_K_FORWARD)
1385    {
1386      arg->num_non_forwards++;
1387      ctf_dprintf ("Counting hash %s: kind %i: num_non_forwards is %i\n",
1388		   hval, kind, arg->num_non_forwards);
1389    }
1390
1391  /* We only need to know if there is more than one non-forward (an ambiguous
1392     type): don't waste time iterating any more than needed to figure that
1393     out.  */
1394
1395  if (arg->num_non_forwards > 1)
1396    return 1;
1397
1398  return 0;
1399}
1400
1401/* Detect name ambiguity and mark ambiguous names as conflicting, other than the
1402   most common.  */
1403static int
1404ctf_dedup_detect_name_ambiguity (ctf_file_t *fp, ctf_file_t **inputs)
1405{
1406  ctf_dedup_t *d = &fp->ctf_dedup;
1407  ctf_next_t *i = NULL;
1408  void *k;
1409  void *v;
1410  int err;
1411  const char *whaterr;
1412
1413  /* Go through cd_name_counts for all CTF namespaces in turn.  */
1414
1415  while ((err = ctf_dynhash_next (d->cd_name_counts, &i, &k, &v)) == 0)
1416    {
1417      const char *decorated = (const char *) k;
1418      ctf_dynhash_t *name_counts = (ctf_dynhash_t *) v;
1419      ctf_next_t *j = NULL;
1420
1421      /* If this is a forwardable kind or a forward (which we can tell without
1422	 consulting the type because its decorated name has a space as its
1423	 second character: see ctf_decorate_type_name), we are only interested
1424	 in whether this name has many hashes associated with it: any such name
1425	 is necessarily ambiguous, and types with that name are conflicting.
1426	 Once we know whether this is true, we can skip to the next name: so use
1427	 ctf_dynhash_iter_find for efficiency.  */
1428
1429      if (decorated[0] != '\0' && decorated[1] == ' ')
1430	{
1431	  ctf_dedup_type_counter_t counters = { fp, inputs, 0 };
1432	  ctf_dynhash_t *counts = (ctf_dynhash_t *) v;
1433
1434	  ctf_dynhash_iter_find (counts, ctf_dedup_count_types, &counters);
1435
1436	  /* Check for assertion failure and pass it up.  */
1437	  if (ctf_errno (fp) == ECTF_INTERNAL)
1438	    goto assert_err;
1439
1440	  if (counters.num_non_forwards > 1)
1441	    {
1442	      const void *hval_;
1443
1444	      while ((err = ctf_dynhash_cnext (counts, &j, &hval_, NULL)) == 0)
1445		{
1446		  const char *hval = (const char *) hval_;
1447		  ctf_dynset_t *type_ids;
1448		  void *id;
1449		  int kind;
1450
1451		  /* Dig through the types in this hash to find the non-forwards
1452		     and mark them ambiguous.  */
1453
1454		  type_ids = ctf_dynhash_lookup (d->cd_output_mapping, hval);
1455
1456		  /* Nonexistent? Must be a forward with no referent.  */
1457		  if (!type_ids)
1458		    continue;
1459
1460		  id = ctf_dynset_lookup_any (type_ids);
1461
1462		  kind = ctf_type_kind (inputs[CTF_DEDUP_GID_TO_INPUT (id)],
1463					CTF_DEDUP_GID_TO_TYPE (id));
1464
1465		  if (kind != CTF_K_FORWARD)
1466		    {
1467		      ctf_dprintf ("Marking %p, with hash %s, conflicting: one "
1468				   "of many non-forward GIDs for %s\n", id,
1469				   hval, (char *) k);
1470		      ctf_dedup_mark_conflicting_hash (fp, hval);
1471		    }
1472		}
1473	      if (err != ECTF_NEXT_END)
1474		{
1475		  whaterr = N_("error marking conflicting structs/unions");
1476		  goto iterr;
1477		}
1478	    }
1479	}
1480      else
1481	{
1482	  /* This is an ordinary type.  Find the most common type with this
1483	     name, and mark it unconflicting: all others are conflicting.  (We
1484	     cannot do this sort of popularity contest with forwardable types
1485	     because any forwards to that type would be immediately unified with
1486	     the most-popular type on insertion, and we want conflicting structs
1487	     et al to have all forwards left intact, so the user is notified
1488	     that this type is conflicting.  TODO: improve this in future by
1489	     setting such forwards non-root-visible.)  */
1490
1491	  const void *key;
1492	  const void *count;
1493	  const char *hval;
1494	  long max_hcount = -1;
1495	  const char *max_hval = NULL;
1496
1497	  if (ctf_dynhash_elements (name_counts) <= 1)
1498	    continue;
1499
1500	  /* First find the most common.  */
1501	  while ((err = ctf_dynhash_cnext (name_counts, &j, &key, &count)) == 0)
1502	    {
1503	      hval = (const char *) key;
1504	      if ((long int) (uintptr_t) count > max_hcount)
1505		{
1506		  max_hcount = (long int) (uintptr_t) count;
1507		  max_hval = hval;
1508		}
1509	    }
1510	  if (err != ECTF_NEXT_END)
1511	    {
1512	      whaterr = N_("error finding commonest conflicting type");
1513	      goto iterr;
1514	    }
1515
1516	  /* Mark all the others as conflicting.   */
1517	  while ((err = ctf_dynhash_cnext (name_counts, &j, &key, NULL)) == 0)
1518	    {
1519	      hval = (const char *) key;
1520	      if (strcmp (max_hval, hval) == 0)
1521		continue;
1522
1523	      ctf_dprintf ("Marking %s, an uncommon hash for %s, conflicting\n",
1524			   hval, (const char *) k);
1525	      if (ctf_dedup_mark_conflicting_hash (fp, hval) < 0)
1526		{
1527		  whaterr = N_("error marking hashes as conflicting");
1528		  goto err;
1529		}
1530	    }
1531	  if (err != ECTF_NEXT_END)
1532	    {
1533	      whaterr = N_("marking uncommon conflicting types");
1534	      goto iterr;
1535	    }
1536	}
1537    }
1538  if (err != ECTF_NEXT_END)
1539    {
1540      whaterr = N_("scanning for ambiguous names");
1541      goto iterr;
1542    }
1543
1544  return 0;
1545
1546 err:
1547  ctf_next_destroy (i);
1548  ctf_err_warn (fp, 0, 0, "%s", gettext (whaterr));
1549  return -1;					/* errno is set for us.  */
1550
1551 iterr:
1552  ctf_err_warn (fp, 0, err, _("iteration failed: %s"), gettext (whaterr));
1553  return ctf_set_errno (fp, err);
1554
1555 assert_err:
1556  ctf_next_destroy (i);
1557  return -1; 					/* errno is set for us.  */
1558}
1559
1560/* Initialize the deduplication machinery.  */
1561
1562static int
1563ctf_dedup_init (ctf_file_t *fp)
1564{
1565  ctf_dedup_t *d = &fp->ctf_dedup;
1566  size_t i;
1567
1568  if (ctf_dedup_atoms_init (fp) < 0)
1569      goto oom;
1570
1571#if IDS_NEED_ALLOCATION
1572  if ((d->cd_id_to_file_t = ctf_dynhash_create (ctf_hash_type_id_key,
1573						ctf_hash_eq_type_id_key,
1574						free, NULL)) == NULL)
1575    goto oom;
1576#endif
1577
1578  for (i = 0; i < 4; i++)
1579    {
1580      if ((d->cd_decorated_names[i] = ctf_dynhash_create (ctf_hash_string,
1581							  ctf_hash_eq_string,
1582							  NULL, NULL)) == NULL)
1583	goto oom;
1584    }
1585
1586  if ((d->cd_name_counts
1587       = ctf_dynhash_create (ctf_hash_string,
1588			     ctf_hash_eq_string, NULL,
1589			     (ctf_hash_free_fun) ctf_dynhash_destroy)) == NULL)
1590    goto oom;
1591
1592  if ((d->cd_type_hashes
1593       = ctf_dynhash_create (ctf_hash_integer,
1594			     ctf_hash_eq_integer,
1595			     NULL, NULL)) == NULL)
1596    goto oom;
1597
1598  if ((d->cd_struct_origin
1599       = ctf_dynhash_create (ctf_hash_string,
1600			     ctf_hash_eq_string,
1601			     NULL, NULL)) == NULL)
1602    goto oom;
1603
1604  if ((d->cd_citers
1605       = ctf_dynhash_create (ctf_hash_string,
1606			     ctf_hash_eq_string, NULL,
1607			     (ctf_hash_free_fun) ctf_dynset_destroy)) == NULL)
1608    goto oom;
1609
1610  if ((d->cd_output_mapping
1611       = ctf_dynhash_create (ctf_hash_string,
1612			     ctf_hash_eq_string, NULL,
1613			     (ctf_hash_free_fun) ctf_dynset_destroy)) == NULL)
1614    goto oom;
1615
1616  if ((d->cd_output_first_gid
1617       = ctf_dynhash_create (ctf_hash_string,
1618			     ctf_hash_eq_string,
1619			     NULL, NULL)) == NULL)
1620    goto oom;
1621
1622#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1623  if ((d->cd_output_mapping_guard
1624       = ctf_dynhash_create (ctf_hash_integer,
1625			     ctf_hash_eq_integer, NULL, NULL)) == NULL)
1626    goto oom;
1627#endif
1628
1629  if ((d->cd_emission_struct_members
1630       = ctf_dynhash_create (ctf_hash_integer,
1631			     ctf_hash_eq_integer,
1632			     NULL, NULL)) == NULL)
1633    goto oom;
1634
1635  if ((d->cd_conflicting_types
1636       = ctf_dynset_create (htab_hash_string,
1637			    ctf_dynset_eq_string, NULL)) == NULL)
1638    goto oom;
1639
1640  return 0;
1641
1642 oom:
1643  ctf_err_warn (fp, 0, ENOMEM, _("ctf_dedup_init: cannot initialize: "
1644				 "out of memory"));
1645  return ctf_set_errno (fp, ENOMEM);
1646}
1647
1648void
1649ctf_dedup_fini (ctf_file_t *fp, ctf_file_t **outputs, uint32_t noutputs)
1650{
1651  ctf_dedup_t *d = &fp->ctf_dedup;
1652  size_t i;
1653
1654  /* ctf_dedup_atoms is kept across links.  */
1655#if IDS_NEED_ALLOCATION
1656  ctf_dynhash_destroy (d->cd_id_to_file_t);
1657#endif
1658  for (i = 0; i < 4; i++)
1659    ctf_dynhash_destroy (d->cd_decorated_names[i]);
1660  ctf_dynhash_destroy (d->cd_name_counts);
1661  ctf_dynhash_destroy (d->cd_type_hashes);
1662  ctf_dynhash_destroy (d->cd_struct_origin);
1663  ctf_dynhash_destroy (d->cd_citers);
1664  ctf_dynhash_destroy (d->cd_output_mapping);
1665  ctf_dynhash_destroy (d->cd_output_first_gid);
1666#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1667  ctf_dynhash_destroy (d->cd_output_mapping_guard);
1668#endif
1669  ctf_dynhash_destroy (d->cd_emission_struct_members);
1670  ctf_dynset_destroy (d->cd_conflicting_types);
1671
1672  /* Free the per-output state.  */
1673  if (outputs)
1674    {
1675      for (i = 0; i < noutputs; i++)
1676	{
1677	  ctf_dedup_t *od = &outputs[i]->ctf_dedup;
1678	  ctf_dynhash_destroy (od->cd_output_emission_hashes);
1679	  ctf_dynhash_destroy (od->cd_output_emission_conflicted_forwards);
1680	  ctf_file_close (od->cd_output);
1681	}
1682    }
1683  memset (d, 0, sizeof (ctf_dedup_t));
1684}
1685
1686/* Return 1 if this type is cited by multiple input dictionaries.  */
1687
1688static int
1689ctf_dedup_multiple_input_dicts (ctf_file_t *output, ctf_file_t **inputs,
1690				const char *hval)
1691{
1692  ctf_dedup_t *d = &output->ctf_dedup;
1693  ctf_dynset_t *type_ids;
1694  ctf_next_t *i = NULL;
1695  void *id;
1696  ctf_file_t *found = NULL, *relative_found = NULL;
1697  const char *type_id;
1698  ctf_file_t *input_fp;
1699  ctf_id_t input_id;
1700  const char *name;
1701  const char *decorated;
1702  int fwdkind;
1703  int multiple = 0;
1704  int err;
1705
1706  type_ids = ctf_dynhash_lookup (d->cd_output_mapping, hval);
1707  if (!ctf_assert (output, type_ids))
1708    return -1;
1709
1710  /* Scan across the IDs until we find proof that two disjoint dictionaries
1711     are referenced.  Exit as soon as possible.  Optimization opportunity, but
1712     possibly not worth it, given that this is only executed in
1713     CTF_LINK_SHARE_DUPLICATED mode.  */
1714
1715  while ((err = ctf_dynset_next (type_ids, &i, &id)) == 0)
1716    {
1717      ctf_file_t *fp = inputs[CTF_DEDUP_GID_TO_INPUT (id)];
1718
1719      if (fp == found || fp == relative_found)
1720	continue;
1721
1722      if (!found)
1723	{
1724	  found = fp;
1725	  continue;
1726	}
1727
1728      if (!relative_found
1729	  && (fp->ctf_parent == found || found->ctf_parent == fp))
1730	{
1731	  relative_found = fp;
1732	  continue;
1733	}
1734
1735      multiple = 1;
1736      ctf_next_destroy (i);
1737      break;
1738    }
1739  if ((err != ECTF_NEXT_END) && (err != 0))
1740    {
1741      ctf_err_warn (output, 0, err, _("iteration error "
1742				      "propagating conflictedness"));
1743      return ctf_set_errno (output, err);
1744    }
1745
1746  if (multiple)
1747    return multiple;
1748
1749  /* This type itself does not appear in multiple input dicts: how about another
1750     related type with the same name (e.g. a forward if this is a struct,
1751     etc).  */
1752
1753  type_id = ctf_dynset_lookup_any (type_ids);
1754  if (!ctf_assert (output, type_id))
1755    return -1;
1756
1757  input_fp = inputs[CTF_DEDUP_GID_TO_INPUT (type_id)];
1758  input_id = CTF_DEDUP_GID_TO_TYPE (type_id);
1759  fwdkind = ctf_type_kind_forwarded (input_fp, input_id);
1760  name = ctf_type_name_raw (input_fp, input_id);
1761
1762  if ((fwdkind == CTF_K_STRUCT || fwdkind == CTF_K_UNION)
1763      && name && name[0] != '\0')
1764    {
1765      const void *origin;
1766
1767      if ((decorated = ctf_decorate_type_name (output, name,
1768					       fwdkind)) == NULL)
1769	return -1;				/* errno is set for us.  */
1770
1771      origin = ctf_dynhash_lookup (d->cd_struct_origin, decorated);
1772      if ((origin != NULL) && (CTF_DEDUP_GID_TO_INPUT (origin) < 0))
1773	multiple = 1;
1774    }
1775
1776  return multiple;
1777}
1778
1779/* Demote unconflicting types which reference only one input, or which reference
1780   two inputs where one input is the parent of the other, into conflicting
1781   types.  Only used if the link mode is CTF_LINK_SHARE_DUPLICATED.  */
1782
1783static int
1784ctf_dedup_conflictify_unshared (ctf_file_t *output, ctf_file_t **inputs)
1785{
1786  ctf_dedup_t *d = &output->ctf_dedup;
1787  ctf_next_t *i = NULL;
1788  int err;
1789  const void *k;
1790  ctf_dynset_t *to_mark = NULL;
1791
1792  if ((to_mark = ctf_dynset_create (htab_hash_string, ctf_dynset_eq_string,
1793				    NULL)) == NULL)
1794    goto err_no;
1795
1796  while ((err = ctf_dynhash_cnext (d->cd_output_mapping, &i, &k, NULL)) == 0)
1797    {
1798      const char *hval = (const char *) k;
1799      int conflicting;
1800
1801      /* Types referenced by only one dict, with no type appearing under that
1802	 name elsewhere, are marked conflicting.  */
1803
1804      conflicting = !ctf_dedup_multiple_input_dicts (output, inputs, hval);
1805
1806      if (conflicting < 0)
1807	goto err;				/* errno is set for us.  */
1808
1809      if (conflicting)
1810	if (ctf_dynset_cinsert (to_mark, hval) < 0)
1811	  goto err;
1812    }
1813  if (err != ECTF_NEXT_END)
1814    goto iterr;
1815
1816  while ((err = ctf_dynset_cnext (to_mark, &i, &k)) == 0)
1817    {
1818      const char *hval = (const char *) k;
1819
1820      if (ctf_dedup_mark_conflicting_hash (output, hval) < 0)
1821	goto err;
1822    }
1823  if (err != ECTF_NEXT_END)
1824    goto iterr;
1825
1826  ctf_dynset_destroy (to_mark);
1827
1828  return 0;
1829
1830 err_no:
1831  ctf_set_errno (output, errno);
1832 err:
1833  err = ctf_errno (output);
1834  ctf_next_destroy (i);
1835 iterr:
1836  ctf_dynset_destroy (to_mark);
1837  ctf_err_warn (output, 0, err, _("conflictifying unshared types"));
1838  return ctf_set_errno (output, err);
1839}
1840
1841/* The core deduplicator.  Populate cd_output_mapping in the output ctf_dedup
1842   with a mapping of all types that belong in this dictionary and where they
1843   come from, and cd_conflicting_types with an indication of whether each type
1844   is conflicted or not.  OUTPUT is the top-level output: INPUTS is the array of
1845   input dicts; NINPUTS is the size of that array; PARENTS is an NINPUTS-element
1846   array with each element corresponding to a input which is a child dict set to
1847   the number in the INPUTS array of that input's parent.
1848
1849   If CU_MAPPED is set, this is a first pass for a link with a non-empty CU
1850   mapping: only one output will result.
1851
1852   Only deduplicates: does not emit the types into the output.  Call
1853   ctf_dedup_emit afterwards to do that.  */
1854
1855int
1856ctf_dedup (ctf_file_t *output, ctf_file_t **inputs, uint32_t ninputs,
1857	   uint32_t *parents, int cu_mapped)
1858{
1859  ctf_dedup_t *d = &output->ctf_dedup;
1860  size_t i;
1861  ctf_next_t *it = NULL;
1862
1863  for (i = 0; i < ninputs; i++)
1864    ctf_dprintf ("Input %i: %s\n", (int) i, ctf_link_input_name (inputs[i]));
1865
1866  if (ctf_dedup_init (output) < 0)
1867    return -1; 					/* errno is set for us.  */
1868
1869  /* Some flags do not apply when CU-mapping: this is not a duplicated link,
1870     because there is only one output and we really don't want to end up marking
1871     all nonconflicting but appears-only-once types as conflicting (which in the
1872     CU-mapped link means we'd mark them all as non-root-visible!).  */
1873  d->cd_link_flags = output->ctf_link_flags;
1874  if (cu_mapped)
1875    d->cd_link_flags &= ~(CTF_LINK_SHARE_DUPLICATED);
1876
1877  /* Compute hash values for all types, recursively, treating child structures
1878     and unions equivalent to forwards, and hashing in the name of the referent
1879     of each such type into structures, unions, and non-opaque forwards.
1880     Populate a mapping from decorated name (including an indication of
1881     struct/union/enum namespace) to count of type hash values in
1882     cd_name_counts, a mapping from and a mapping from hash values to input type
1883     IDs in cd_output_mapping.  */
1884
1885  ctf_dprintf ("Computing type hashes\n");
1886  for (i = 0; i < ninputs; i++)
1887    {
1888      ctf_id_t id;
1889
1890      while ((id = ctf_type_next (inputs[i], &it, NULL, 1)) != CTF_ERR)
1891	{
1892	  ctf_dedup_hash_type (output, inputs[i], inputs, parents,
1893			       i, id, 0, 0, ctf_dedup_populate_mappings);
1894	}
1895      if (ctf_errno (inputs[i]) != ECTF_NEXT_END)
1896	{
1897	  ctf_set_errno (output, ctf_errno (inputs[i]));
1898	  ctf_err_warn (output, 0, 0, _("iteration failure "
1899					"computing type hashes"));
1900	  return -1;
1901	}
1902    }
1903
1904  /* Go through the cd_name_counts name->hash->count mapping for all CTF
1905     namespaces: any name with many hashes associated with it at this stage is
1906     necessarily ambiguous.  Mark all the hashes except the most common as
1907     conflicting in the output.  */
1908
1909  ctf_dprintf ("Detecting type name ambiguity\n");
1910  if (ctf_dedup_detect_name_ambiguity (output, inputs) < 0)
1911    return -1;					/* errno is set for us.  */
1912
1913  /* If the link mode is CTF_LINK_SHARE_DUPLICATED, we change any unconflicting
1914     types whose output mapping references only one input dict into a
1915     conflicting type, so that they end up in the per-CU dictionaries.  */
1916
1917  if (d->cd_link_flags & CTF_LINK_SHARE_DUPLICATED)
1918    {
1919      ctf_dprintf ("Conflictifying unshared types\n");
1920      if (ctf_dedup_conflictify_unshared (output, inputs) < 0)
1921	return -1;				/* errno is set for us.  */
1922    }
1923  return 0;
1924}
1925
1926static int
1927ctf_dedup_rwalk_output_mapping (ctf_file_t *output, ctf_file_t **inputs,
1928				uint32_t ninputs, uint32_t *parents,
1929				ctf_dynset_t *already_visited,
1930				const char *hval,
1931				int (*visit_fun) (const char *hval,
1932						  ctf_file_t *output,
1933						  ctf_file_t **inputs,
1934						  uint32_t ninputs,
1935						  uint32_t *parents,
1936						  int already_visited,
1937						  ctf_file_t *input,
1938						  ctf_id_t type,
1939						  void *id,
1940						  int depth,
1941						  void *arg),
1942				void *arg, unsigned long depth);
1943
1944/* Like ctf_dedup_rwalk_output_mapping (which see), only takes a single target
1945   type and visits it.  */
1946static int
1947ctf_dedup_rwalk_one_output_mapping (ctf_file_t *output,
1948				    ctf_file_t **inputs, uint32_t ninputs,
1949				    uint32_t *parents,
1950				    ctf_dynset_t *already_visited,
1951				    int visited, void *type_id,
1952				    const char *hval,
1953				    int (*visit_fun) (const char *hval,
1954						      ctf_file_t *output,
1955						      ctf_file_t **inputs,
1956						      uint32_t ninputs,
1957						      uint32_t *parents,
1958						      int already_visited,
1959						      ctf_file_t *input,
1960						      ctf_id_t type,
1961						      void *id,
1962						      int depth,
1963						      void *arg),
1964				    void *arg, unsigned long depth)
1965{
1966  ctf_dedup_t *d = &output->ctf_dedup;
1967  ctf_file_t *fp;
1968  int input_num;
1969  ctf_id_t type;
1970  int ret;
1971  const char *whaterr;
1972
1973  input_num = CTF_DEDUP_GID_TO_INPUT (type_id);
1974  fp = inputs[input_num];
1975  type = CTF_DEDUP_GID_TO_TYPE (type_id);
1976
1977  ctf_dprintf ("%lu: Starting walk over type %s, %i/%lx (%p), from %s, "
1978	       "kind %i\n", depth, hval, input_num, type, (void *) fp,
1979	       ctf_link_input_name (fp), ctf_type_kind_unsliced (fp, type));
1980
1981  /* Get the single call we do if this type has already been visited out of the
1982     way.  */
1983  if (visited)
1984    return visit_fun (hval, output, inputs, ninputs, parents, visited, fp,
1985		      type, type_id, depth, arg);
1986
1987  /* This macro is really ugly, but the alternative is repeating this code many
1988     times, which is worse.  */
1989
1990#define CTF_TYPE_WALK(type, errlabel, errmsg)				\
1991  do {									\
1992    void *type_id;							\
1993    const char *hashval;						\
1994    int cited_type_input_num = input_num;				\
1995									\
1996    if ((fp->ctf_flags & LCTF_CHILD) && (LCTF_TYPE_ISPARENT (fp, type))) \
1997      cited_type_input_num = parents[input_num];			\
1998									\
1999    type_id = CTF_DEDUP_GID (output, cited_type_input_num, type);	\
2000									\
2001    if (type == 0)							\
2002      {									\
2003	ctf_dprintf ("Walking: unimplemented type\n");			\
2004	break;								\
2005      }									\
2006									\
2007    ctf_dprintf ("Looking up ID %i/%lx in type hashes\n",		\
2008		 cited_type_input_num, type);				\
2009    hashval = ctf_dynhash_lookup (d->cd_type_hashes, type_id);		\
2010    if (!ctf_assert (output, hashval))					\
2011      {									\
2012	whaterr = N_("error looking up ID in type hashes");		\
2013	goto errlabel;							\
2014      }									\
2015    ctf_dprintf ("ID %i/%lx has hash %s\n", cited_type_input_num, type,	\
2016		 hashval);						\
2017									\
2018    ret = ctf_dedup_rwalk_output_mapping (output, inputs, ninputs, parents, \
2019					  already_visited, hashval,	\
2020					  visit_fun, arg, depth);	\
2021    if (ret < 0)							\
2022      {									\
2023	whaterr = errmsg;						\
2024	goto errlabel;							\
2025      }									\
2026  } while (0)
2027
2028  switch (ctf_type_kind_unsliced (fp, type))
2029    {
2030    case CTF_K_UNKNOWN:
2031      /* Just skip things of unknown kind.  */
2032      return 0;
2033    case CTF_K_FORWARD:
2034    case CTF_K_INTEGER:
2035    case CTF_K_FLOAT:
2036    case CTF_K_ENUM:
2037      /* No types referenced.  */
2038      break;
2039
2040    case CTF_K_TYPEDEF:
2041    case CTF_K_VOLATILE:
2042    case CTF_K_CONST:
2043    case CTF_K_RESTRICT:
2044    case CTF_K_POINTER:
2045    case CTF_K_SLICE:
2046      CTF_TYPE_WALK (ctf_type_reference (fp, type), err,
2047		     N_("error during referenced type walk"));
2048      break;
2049
2050    case CTF_K_ARRAY:
2051      {
2052	ctf_arinfo_t ar;
2053
2054	if (ctf_array_info (fp, type, &ar) < 0)
2055	  {
2056	    whaterr = N_("error during array info lookup");
2057	    goto err_msg;
2058	  }
2059
2060	CTF_TYPE_WALK (ar.ctr_contents, err,
2061		       N_("error during array contents type walk"));
2062	CTF_TYPE_WALK (ar.ctr_index, err,
2063		       N_("error during array index type walk"));
2064	break;
2065      }
2066
2067    case CTF_K_FUNCTION:
2068      {
2069	ctf_funcinfo_t fi;
2070	ctf_id_t *args;
2071	uint32_t j;
2072
2073	if (ctf_func_type_info (fp, type, &fi) < 0)
2074	  {
2075	    whaterr = N_("error during func type info lookup");
2076	    goto err_msg;
2077	  }
2078
2079	CTF_TYPE_WALK (fi.ctc_return, err,
2080		       N_("error during func return type walk"));
2081
2082	if ((args = calloc (fi.ctc_argc, sizeof (ctf_id_t))) == NULL)
2083	  {
2084	    whaterr = N_("error doing memory allocation");
2085	    goto err_msg;
2086	  }
2087
2088	if (ctf_func_type_args (fp, type, fi.ctc_argc, args) < 0)
2089	  {
2090	    whaterr = N_("error doing func arg type lookup");
2091	    free (args);
2092	    goto err_msg;
2093	  }
2094
2095	for (j = 0; j < fi.ctc_argc; j++)
2096	  CTF_TYPE_WALK (args[j], err_free_args,
2097			 N_("error during Func arg type walk"));
2098	free (args);
2099	break;
2100
2101      err_free_args:
2102	free (args);
2103	goto err;
2104      }
2105    case CTF_K_STRUCT:
2106    case CTF_K_UNION:
2107      /* We do not recursively traverse the members of structures: they are
2108	 emitted later, in a separate pass.  */
2109	break;
2110    default:
2111      whaterr = N_("CTF dict corruption: unknown type kind");
2112      goto err_msg;
2113    }
2114
2115  return visit_fun (hval, output, inputs, ninputs, parents, visited, fp, type,
2116		    type_id, depth, arg);
2117
2118 err_msg:
2119  ctf_set_errno (output, ctf_errno (fp));
2120  ctf_err_warn (output, 0, 0, _("%s in input file %s at type ID %lx"),
2121		gettext (whaterr), ctf_link_input_name (fp), type);
2122 err:
2123  return -1;
2124}
2125/* Recursively traverse the output mapping, and do something with each type
2126   visited, from leaves to root.  VISIT_FUN, called as recursion unwinds,
2127   returns a negative error code or zero.  Type hashes may be visited more than
2128   once, but are not recursed through repeatedly: ALREADY_VISITED tracks whether
2129   types have already been visited.  */
2130static int
2131ctf_dedup_rwalk_output_mapping (ctf_file_t *output, ctf_file_t **inputs,
2132				uint32_t ninputs, uint32_t *parents,
2133				ctf_dynset_t *already_visited,
2134				const char *hval,
2135				int (*visit_fun) (const char *hval,
2136						  ctf_file_t *output,
2137						  ctf_file_t **inputs,
2138						  uint32_t ninputs,
2139						  uint32_t *parents,
2140						  int already_visited,
2141						  ctf_file_t *input,
2142						  ctf_id_t type,
2143						  void *id,
2144						  int depth,
2145						  void *arg),
2146				void *arg, unsigned long depth)
2147{
2148  ctf_dedup_t *d = &output->ctf_dedup;
2149  ctf_next_t *i = NULL;
2150  int err;
2151  int visited = 1;
2152  ctf_dynset_t *type_ids;
2153  void *id;
2154
2155  depth++;
2156
2157  type_ids = ctf_dynhash_lookup (d->cd_output_mapping, hval);
2158  if (!type_ids)
2159    {
2160      ctf_err_warn (output, 0, ECTF_INTERNAL,
2161		    _("looked up type kind by nonexistent hash %s"), hval);
2162      return ctf_set_errno (output, ECTF_INTERNAL);
2163    }
2164
2165  /* Have we seen this type before?  */
2166
2167  if (!ctf_dynset_exists (already_visited, hval, NULL))
2168    {
2169      /* Mark as already-visited immediately, to eliminate the possibility of
2170	 cycles: but remember we have not actually visited it yet for the
2171	 upcoming call to the visit_fun.  (All our callers handle cycles
2172	 properly themselves, so we can just abort them aggressively as soon as
2173	 we find ourselves in one.)  */
2174
2175      visited = 0;
2176      if (ctf_dynset_cinsert (already_visited, hval) < 0)
2177	{
2178	  ctf_err_warn (output, 0, ENOMEM,
2179			_("out of memory tracking already-visited types"));
2180	  return ctf_set_errno (output, ENOMEM);
2181	}
2182    }
2183
2184  /* If this type is marked conflicted, traverse members and call
2185     ctf_dedup_rwalk_output_mapping_once on all the unique ones: otherwise, just
2186     pick a random one and use it.  */
2187
2188  if (!ctf_dynset_exists (d->cd_conflicting_types, hval, NULL))
2189    {
2190      id = ctf_dynset_lookup_any (type_ids);
2191      if (!ctf_assert (output, id))
2192	return -1;
2193
2194      return ctf_dedup_rwalk_one_output_mapping (output, inputs, ninputs,
2195						 parents, already_visited,
2196						 visited, id, hval, visit_fun,
2197						 arg, depth);
2198    }
2199
2200  while ((err = ctf_dynset_next (type_ids, &i, &id)) == 0)
2201    {
2202      int ret;
2203
2204      ret = ctf_dedup_rwalk_one_output_mapping (output, inputs, ninputs,
2205						parents, already_visited,
2206						visited, id, hval,
2207						visit_fun, arg, depth);
2208      if (ret < 0)
2209	{
2210	  ctf_next_destroy (i);
2211	  return ret;				/* errno is set for us.  */
2212	}
2213    }
2214  if (err != ECTF_NEXT_END)
2215    {
2216      ctf_err_warn (output, 0, err, _("cannot walk conflicted type"));
2217      return ctf_set_errno (output, err);
2218    }
2219
2220  return 0;
2221}
2222
2223typedef struct ctf_sort_om_cb_arg
2224{
2225  ctf_file_t **inputs;
2226  uint32_t ninputs;
2227  ctf_dedup_t *d;
2228} ctf_sort_om_cb_arg_t;
2229
2230/* Sort the output mapping into order: types first appearing in earlier inputs
2231   first, parents preceding children: if types first appear in the same input,
2232   sort those with earlier ctf_id_t's first.  */
2233static int
2234sort_output_mapping (const ctf_next_hkv_t *one, const ctf_next_hkv_t *two,
2235		     void *arg_)
2236{
2237  ctf_sort_om_cb_arg_t *arg = (ctf_sort_om_cb_arg_t *) arg_;
2238  ctf_dedup_t *d = arg->d;
2239  const char *one_hval = (const char *) one->hkv_key;
2240  const char *two_hval = (const char *) two->hkv_key;
2241  void *one_gid, *two_gid;
2242  uint32_t one_ninput;
2243  uint32_t two_ninput;
2244  ctf_file_t *one_fp;
2245  ctf_file_t *two_fp;
2246  ctf_id_t one_type;
2247  ctf_id_t two_type;
2248
2249  one_gid = ctf_dynhash_lookup (d->cd_output_first_gid, one_hval);
2250  two_gid = ctf_dynhash_lookup (d->cd_output_first_gid, two_hval);
2251
2252  one_ninput = CTF_DEDUP_GID_TO_INPUT (one_gid);
2253  two_ninput = CTF_DEDUP_GID_TO_INPUT (two_gid);
2254
2255  one_type = CTF_DEDUP_GID_TO_TYPE (one_gid);
2256  two_type = CTF_DEDUP_GID_TO_TYPE (two_gid);
2257
2258  /* It's kind of hard to smuggle an assertion failure out of here.  */
2259  assert (one_ninput < arg->ninputs && two_ninput < arg->ninputs);
2260
2261  one_fp = arg->inputs[one_ninput];
2262  two_fp = arg->inputs[two_ninput];
2263
2264  /* Parents before children.  */
2265
2266  if (!(one_fp->ctf_flags & LCTF_CHILD)
2267      && (two_fp->ctf_flags & LCTF_CHILD))
2268    return -1;
2269  else if ((one_fp->ctf_flags & LCTF_CHILD)
2270      && !(two_fp->ctf_flags & LCTF_CHILD))
2271    return 1;
2272
2273  /* ninput order, types appearing in earlier TUs first.  */
2274
2275  if (one_ninput < two_ninput)
2276    return -1;
2277  else if (two_ninput < one_ninput)
2278    return 1;
2279
2280  /* Same TU.  Earliest ctf_id_t first.  They cannot be the same.  */
2281
2282  assert (one_type != two_type);
2283  if (one_type < two_type)
2284    return -1;
2285  else
2286    return 1;
2287}
2288
2289/* The public entry point to ctf_dedup_rwalk_output_mapping, above.  */
2290static int
2291ctf_dedup_walk_output_mapping (ctf_file_t *output, ctf_file_t **inputs,
2292			       uint32_t ninputs, uint32_t *parents,
2293			       int (*visit_fun) (const char *hval,
2294						 ctf_file_t *output,
2295						 ctf_file_t **inputs,
2296						 uint32_t ninputs,
2297						 uint32_t *parents,
2298						 int already_visited,
2299						 ctf_file_t *input,
2300						 ctf_id_t type,
2301						 void *id,
2302						 int depth,
2303						 void *arg),
2304			       void *arg)
2305{
2306  ctf_dynset_t *already_visited;
2307  ctf_next_t *i = NULL;
2308  ctf_sort_om_cb_arg_t sort_arg;
2309  int err;
2310  void *k;
2311
2312  if ((already_visited = ctf_dynset_create (htab_hash_string,
2313					    ctf_dynset_eq_string,
2314					    NULL)) == NULL)
2315    return ctf_set_errno (output, ENOMEM);
2316
2317  sort_arg.inputs = inputs;
2318  sort_arg.ninputs = ninputs;
2319  sort_arg.d = &output->ctf_dedup;
2320
2321  while ((err = ctf_dynhash_next_sorted (output->ctf_dedup.cd_output_mapping,
2322					 &i, &k, NULL, sort_output_mapping,
2323					 &sort_arg)) == 0)
2324    {
2325      const char *hval = (const char *) k;
2326
2327      err = ctf_dedup_rwalk_output_mapping (output, inputs, ninputs, parents,
2328					    already_visited, hval, visit_fun,
2329					    arg, 0);
2330      if (err < 0)
2331	{
2332	  ctf_next_destroy (i);
2333	  goto err;				/* errno is set for us.  */
2334	}
2335    }
2336  if (err != ECTF_NEXT_END)
2337    {
2338      ctf_err_warn (output, 0, err, _("cannot recurse over output mapping"));
2339      ctf_set_errno (output, err);
2340      goto err;
2341    }
2342  ctf_dynset_destroy (already_visited);
2343
2344  return 0;
2345 err:
2346  ctf_dynset_destroy (already_visited);
2347  return -1;
2348}
2349
2350/* Possibly synthesise a synthetic forward in TARGET to subsitute for a
2351   conflicted per-TU type ID in INPUT with hash HVAL.  Return its CTF ID, or 0
2352   if none was needed.  */
2353static ctf_id_t
2354ctf_dedup_maybe_synthesize_forward (ctf_file_t *output, ctf_file_t *target,
2355				    ctf_file_t *input, ctf_id_t id,
2356				    const char *hval)
2357{
2358  ctf_dedup_t *od = &output->ctf_dedup;
2359  ctf_dedup_t *td = &target->ctf_dedup;
2360  int kind;
2361  int fwdkind;
2362  const char *name;
2363  const char *decorated;
2364  void *v;
2365  ctf_id_t emitted_forward;
2366
2367  if (!ctf_dynset_exists (od->cd_conflicting_types, hval, NULL)
2368      || target->ctf_flags & LCTF_CHILD
2369      || !ctf_type_name_raw (input, id)
2370      || (((kind = ctf_type_kind_unsliced (input, id)) != CTF_K_STRUCT
2371	   && kind != CTF_K_UNION && kind != CTF_K_FORWARD)))
2372    return 0;
2373
2374  fwdkind = ctf_type_kind_forwarded (input, id);
2375  name = ctf_type_name_raw (input, id);
2376
2377  ctf_dprintf ("Using synthetic forward for conflicted struct/union with "
2378	       "hval %s\n", hval);
2379
2380  if (!ctf_assert (output, name))
2381    return CTF_ERR;
2382
2383  if ((decorated = ctf_decorate_type_name (output, name, fwdkind)) == NULL)
2384    return CTF_ERR;
2385
2386  if (!ctf_dynhash_lookup_kv (td->cd_output_emission_conflicted_forwards,
2387			      decorated, NULL, &v))
2388    {
2389      if ((emitted_forward = ctf_add_forward (target, CTF_ADD_ROOT, name,
2390					      fwdkind)) == CTF_ERR)
2391	{
2392	  ctf_set_errno (output, ctf_errno (target));
2393	  return CTF_ERR;
2394	}
2395
2396      if (ctf_dynhash_cinsert (td->cd_output_emission_conflicted_forwards,
2397			       decorated, (void *) (uintptr_t)
2398			       emitted_forward) < 0)
2399	{
2400	  ctf_set_errno (output, ENOMEM);
2401	  return CTF_ERR;
2402	}
2403    }
2404  else
2405    emitted_forward = (ctf_id_t) (uintptr_t) v;
2406
2407  ctf_dprintf ("Cross-TU conflicted struct: passing back forward, %lx\n",
2408	       emitted_forward);
2409
2410  return emitted_forward;
2411}
2412
2413/* Map a GID in some INPUT dict, in the form of an input number and a ctf_id_t,
2414   into a GID in a target output dict.  If it returns 0, this is the
2415   unimplemented type, and the input type must have been 0.  The OUTPUT dict is
2416   assumed to be the parent of the TARGET, if it is not the TARGET itself.
2417
2418   Returns CTF_ERR on failure.  Responds to an incoming CTF_ERR as an 'id' by
2419   returning CTF_ERR, to simplify callers.  Errors are always propagated to the
2420   input, even if they relate to the target, for the same reason.  (Target
2421   errors are expected to be very rare.)
2422
2423   If the type in question is a citation of a conflicted type in a different TU,
2424   emit a forward of the right type in its place (if not already emitted), and
2425   record that forward in cd_output_emission_conflicted_forwards.  This avoids
2426   the need to replicate the entire type graph below this point in the current
2427   TU (an appalling waste of space).
2428
2429   TODO: maybe replace forwards in the same TU with their referents?  Might
2430   make usability a bit better.  */
2431
2432static ctf_id_t
2433ctf_dedup_id_to_target (ctf_file_t *output, ctf_file_t *target,
2434			ctf_file_t **inputs, uint32_t ninputs,
2435			uint32_t *parents, ctf_file_t *input, int input_num,
2436			ctf_id_t id)
2437{
2438  ctf_dedup_t *od = &output->ctf_dedup;
2439  ctf_dedup_t *td = &target->ctf_dedup;
2440  ctf_file_t *err_fp = input;
2441  const char *hval;
2442  void *target_id;
2443  ctf_id_t emitted_forward;
2444
2445  /* The target type of an error is an error.  */
2446  if (id == CTF_ERR)
2447    return CTF_ERR;
2448
2449  /* The unimplemented type's ID never changes.  */
2450  if (!id)
2451    {
2452      ctf_dprintf ("%i/%lx: unimplemented type\n", input_num, id);
2453      return 0;
2454    }
2455
2456  ctf_dprintf ("Mapping %i/%lx to target %p (%s)\n", input_num,
2457	       id, (void *) target, ctf_link_input_name (target));
2458
2459  /* If the input type is in the parent type space, and this is a child, reset
2460     the input to the parent (which must already have been emitted, since
2461     emission of parent dicts happens before children).  */
2462  if ((input->ctf_flags & LCTF_CHILD) && (LCTF_TYPE_ISPARENT (input, id)))
2463    {
2464      if (!ctf_assert (output, parents[input_num] <= ninputs))
2465	return -1;
2466      input = inputs[parents[input_num]];
2467      input_num = parents[input_num];
2468    }
2469
2470  hval = ctf_dynhash_lookup (od->cd_type_hashes,
2471			     CTF_DEDUP_GID (output, input_num, id));
2472
2473  if (!ctf_assert (output, hval && td->cd_output_emission_hashes))
2474    return -1;
2475
2476  /* If this type is a conflicted tagged structure, union, or forward,
2477     substitute a synthetic forward instead, emitting it if need be.  Only do
2478     this if the target is in the parent dict: if it's in the child dict, we can
2479     just point straight at the thing itself.  Of course, we might be looking in
2480     the child dict right now and not find it and have to look in the parent, so
2481     we have to do this check twice.  */
2482
2483  emitted_forward = ctf_dedup_maybe_synthesize_forward (output, target,
2484							input, id, hval);
2485  switch (emitted_forward)
2486    {
2487    case 0: /* No forward needed.  */
2488      break;
2489    case -1:
2490      ctf_set_errno (err_fp, ctf_errno (output));
2491      ctf_err_warn (err_fp, 0, 0, _("cannot add synthetic forward for type "
2492				    "%i/%lx"), input_num, id);
2493      return -1;
2494    default:
2495      return emitted_forward;
2496    }
2497
2498  ctf_dprintf ("Looking up %i/%lx, hash %s, in target\n", input_num, id, hval);
2499
2500  target_id = ctf_dynhash_lookup (td->cd_output_emission_hashes, hval);
2501  if (!target_id)
2502    {
2503      /* Must be in the parent, so this must be a child, and they must not be
2504	 the same dict.  */
2505      ctf_dprintf ("Checking shared parent for target\n");
2506      if (!ctf_assert (output, (target != output)
2507		       && (target->ctf_flags & LCTF_CHILD)))
2508	return -1;
2509
2510      target_id = ctf_dynhash_lookup (od->cd_output_emission_hashes, hval);
2511
2512      emitted_forward = ctf_dedup_maybe_synthesize_forward (output, output,
2513							    input, id, hval);
2514      switch (emitted_forward)
2515	{
2516	case 0: /* No forward needed.  */
2517	  break;
2518	case -1:
2519	  ctf_err_warn (err_fp, 0, ctf_errno (output),
2520			_("cannot add synthetic forward for type %i/%lx"),
2521			input_num, id);
2522	  return ctf_set_errno (err_fp, ctf_errno (output));
2523	default:
2524	  return emitted_forward;
2525	}
2526    }
2527  if (!ctf_assert (output, target_id))
2528    return -1;
2529  return (ctf_id_t) (uintptr_t) target_id;
2530}
2531
2532/* Emit a single deduplicated TYPE with the given HVAL, located in a given
2533   INPUT, with the given (G)ID, into the shared OUTPUT or a
2534   possibly-newly-created per-CU dict.  All the types this type depends upon
2535   have already been emitted.  (This type itself may also have been emitted.)
2536
2537   If the ARG is 1, this is a CU-mapped deduplication round mapping many
2538   ctf_file_t's into precisely one: conflicting types should be marked
2539   non-root-visible.  If the ARG is 0, conflicting types go into per-CU
2540   dictionaries stored in the input's ctf_dedup.cd_output: otherwise, everything
2541   is emitted directly into the output.  No struct/union members are emitted.
2542
2543   Optimization opportunity: trace the ancestry of non-root-visible types and
2544   elide all that neither have a root-visible type somewhere towards their root,
2545   nor have the type visible via any other route (the function info section,
2546   data object section, backtrace section etc).  */
2547
2548static int
2549ctf_dedup_emit_type (const char *hval, ctf_file_t *output, ctf_file_t **inputs,
2550		     uint32_t ninputs, uint32_t *parents, int already_visited,
2551		     ctf_file_t *input, ctf_id_t type, void *id, int depth,
2552		     void *arg)
2553{
2554  ctf_dedup_t *d = &output->ctf_dedup;
2555  int kind = ctf_type_kind_unsliced (input, type);
2556  const char *name;
2557  ctf_file_t *target = output;
2558  ctf_file_t *real_input;
2559  const ctf_type_t *tp;
2560  int input_num = CTF_DEDUP_GID_TO_INPUT (id);
2561  int output_num = (uint32_t) -1;		/* 'shared' */
2562  int cu_mapped = *(int *)arg;
2563  int isroot = 1;
2564  int is_conflicting;
2565
2566  ctf_next_t *i = NULL;
2567  ctf_id_t new_type;
2568  ctf_id_t ref;
2569  ctf_id_t maybe_dup = 0;
2570  ctf_encoding_t ep;
2571  const char *errtype;
2572  int emission_hashed = 0;
2573
2574  /* We don't want to re-emit something we've already emitted.  */
2575
2576  if (already_visited)
2577    return 0;
2578
2579  ctf_dprintf ("%i: Emitting type with hash %s from %s: determining target\n",
2580	       depth, hval, ctf_link_input_name (input));
2581
2582  /* Conflicting types go into a per-CU output dictionary, unless this is a
2583     CU-mapped run.  The import is not refcounted, since it goes into the
2584     ctf_link_outputs dict of the output that is its parent.  */
2585  is_conflicting = ctf_dynset_exists (d->cd_conflicting_types, hval, NULL);
2586
2587  if (is_conflicting && !cu_mapped)
2588    {
2589      ctf_dprintf ("%i: Type %s in %i/%lx is conflicted: "
2590		   "inserting into per-CU target.\n",
2591		   depth, hval, input_num, type);
2592
2593      if (input->ctf_dedup.cd_output)
2594	target = input->ctf_dedup.cd_output;
2595      else
2596	{
2597	  int err;
2598
2599	  if ((target = ctf_create (&err)) == NULL)
2600	    {
2601	      ctf_err_warn (output, 0, err,
2602			    _("cannot create per-CU CTF archive for CU %s"),
2603			    ctf_link_input_name (input));
2604	      return ctf_set_errno (output, err);
2605	    }
2606
2607	  ctf_import_unref (target, output);
2608	  if (ctf_cuname (input) != NULL)
2609	    ctf_cuname_set (target, ctf_cuname (input));
2610	  else
2611	    ctf_cuname_set (target, "unnamed-CU");
2612	  ctf_parent_name_set (target, _CTF_SECTION);
2613
2614	  input->ctf_dedup.cd_output = target;
2615	}
2616      output_num = input_num;
2617    }
2618
2619  real_input = input;
2620  if ((tp = ctf_lookup_by_id (&real_input, type)) == NULL)
2621    {
2622      ctf_err_warn (output, 0, ctf_errno (input),
2623		    _("%s: lookup failure for type %lx"),
2624		    ctf_link_input_name (real_input), type);
2625      return ctf_set_errno (output, ctf_errno (input));
2626    }
2627
2628  name = ctf_strraw (real_input, tp->ctt_name);
2629
2630  /* Hide conflicting types, if we were asked to: also hide if a type with this
2631     name already exists and is not a forward.  */
2632  if (cu_mapped && is_conflicting)
2633    isroot = 0;
2634  else if (name
2635	   && (maybe_dup = ctf_lookup_by_rawname (target, kind, name)) != 0)
2636    {
2637      if (ctf_type_kind (target, maybe_dup) != CTF_K_FORWARD)
2638	isroot = 0;
2639    }
2640
2641  ctf_dprintf ("%i: Emitting type with hash %s (%s), into target %i/%p\n",
2642	       depth, hval, name ? name : "", input_num, (void *) target);
2643
2644  if (!target->ctf_dedup.cd_output_emission_hashes)
2645    if ((target->ctf_dedup.cd_output_emission_hashes
2646	 = ctf_dynhash_create (ctf_hash_string, ctf_hash_eq_string,
2647			      NULL, NULL)) == NULL)
2648      goto oom_hash;
2649
2650  if (!target->ctf_dedup.cd_output_emission_conflicted_forwards)
2651    if ((target->ctf_dedup.cd_output_emission_conflicted_forwards
2652	 = ctf_dynhash_create (ctf_hash_string, ctf_hash_eq_string,
2653			      NULL, NULL)) == NULL)
2654      goto oom_hash;
2655
2656  switch (kind)
2657    {
2658    case CTF_K_UNKNOWN:
2659      /* These are types that CTF cannot encode, marked as such by the compile.
2660	 We intentionally do not re-emit these.  */
2661      new_type = 0;
2662      break;
2663    case CTF_K_FORWARD:
2664      /* This will do nothing if the type to which this forwards already exists,
2665	 and will be replaced with such a type if it appears later.  */
2666
2667      errtype = _("forward");
2668      if ((new_type = ctf_add_forward (target, isroot, name,
2669				       ctf_type_kind_forwarded (input, type)))
2670	  == CTF_ERR)
2671	goto err_target;
2672      break;
2673
2674    case CTF_K_FLOAT:
2675    case CTF_K_INTEGER:
2676      errtype = _("float/int");
2677      if (ctf_type_encoding (input, type, &ep) < 0)
2678	goto err_input;				/* errno is set for us.  */
2679      if ((new_type = ctf_add_encoded (target, isroot, name, &ep, kind))
2680	  == CTF_ERR)
2681	goto err_target;
2682      break;
2683
2684    case CTF_K_ENUM:
2685      {
2686	int val;
2687	errtype = _("enum");
2688	if ((new_type = ctf_add_enum (target, isroot, name)) == CTF_ERR)
2689	  goto err_input;				/* errno is set for us.  */
2690
2691	while ((name = ctf_enum_next (input, type, &i, &val)) != NULL)
2692	  {
2693	    if (ctf_add_enumerator (target, new_type, name, val) < 0)
2694	      {
2695		ctf_err_warn (target, 0, ctf_errno (target),
2696			      _("%s (%i): cannot add enumeration value %s "
2697				"from input type %lx"),
2698			      ctf_link_input_name (input), input_num, name,
2699			      type);
2700		ctf_next_destroy (i);
2701		return ctf_set_errno (output, ctf_errno (target));
2702	      }
2703	  }
2704	if (ctf_errno (input) != ECTF_NEXT_END)
2705	  goto err_input;
2706	break;
2707      }
2708
2709    case CTF_K_TYPEDEF:
2710      errtype = _("typedef");
2711
2712      ref = ctf_type_reference (input, type);
2713      if ((ref = ctf_dedup_id_to_target (output, target, inputs, ninputs,
2714					 parents, input, input_num,
2715					 ref)) == CTF_ERR)
2716	goto err_input;				/* errno is set for us.  */
2717
2718      if ((new_type = ctf_add_typedef (target, isroot, name, ref)) == CTF_ERR)
2719	goto err_target;			/* errno is set for us.  */
2720      break;
2721
2722    case CTF_K_VOLATILE:
2723    case CTF_K_CONST:
2724    case CTF_K_RESTRICT:
2725    case CTF_K_POINTER:
2726      errtype = _("pointer or cvr-qual");
2727
2728      ref = ctf_type_reference (input, type);
2729      if ((ref = ctf_dedup_id_to_target (output, target, inputs, ninputs,
2730					 parents, input, input_num,
2731					 ref)) == CTF_ERR)
2732	goto err_input;				/* errno is set for us.  */
2733
2734      if ((new_type = ctf_add_reftype (target, isroot, ref, kind)) == CTF_ERR)
2735	goto err_target;			/* errno is set for us.  */
2736      break;
2737
2738    case CTF_K_SLICE:
2739      errtype = _("slice");
2740
2741      if (ctf_type_encoding (input, type, &ep) < 0)
2742	goto err_input;				/* errno is set for us.  */
2743
2744      ref = ctf_type_reference (input, type);
2745      if ((ref = ctf_dedup_id_to_target (output, target, inputs, ninputs,
2746					 parents, input, input_num,
2747					 ref)) == CTF_ERR)
2748	goto err_input;
2749
2750      if ((new_type = ctf_add_slice (target, isroot, ref, &ep)) == CTF_ERR)
2751	goto err_target;
2752      break;
2753
2754    case CTF_K_ARRAY:
2755      {
2756	ctf_arinfo_t ar;
2757
2758	errtype = _("array info");
2759	if (ctf_array_info (input, type, &ar) < 0)
2760	  goto err_input;
2761
2762	ar.ctr_contents = ctf_dedup_id_to_target (output, target, inputs,
2763						  ninputs, parents, input,
2764						  input_num, ar.ctr_contents);
2765	ar.ctr_index = ctf_dedup_id_to_target (output, target, inputs, ninputs,
2766					       parents, input, input_num,
2767					       ar.ctr_index);
2768
2769	if (ar.ctr_contents == CTF_ERR || ar.ctr_index == CTF_ERR)
2770	  goto err_input;
2771
2772	if ((new_type = ctf_add_array (target, isroot, &ar)) == CTF_ERR)
2773	  goto err_target;
2774
2775	break;
2776      }
2777
2778    case CTF_K_FUNCTION:
2779      {
2780	ctf_funcinfo_t fi;
2781	ctf_id_t *args;
2782	uint32_t j;
2783
2784	errtype = _("function");
2785	if (ctf_func_type_info (input, type, &fi) < 0)
2786	  goto err_input;
2787
2788	fi.ctc_return = ctf_dedup_id_to_target (output, target, inputs, ninputs,
2789						parents, input, input_num,
2790						fi.ctc_return);
2791	if (fi.ctc_return == CTF_ERR)
2792	  goto err_input;
2793
2794	if ((args = calloc (fi.ctc_argc, sizeof (ctf_id_t))) == NULL)
2795	  {
2796	    ctf_set_errno (input, ENOMEM);
2797	    goto err_input;
2798	  }
2799
2800	errtype = _("function args");
2801	if (ctf_func_type_args (input, type, fi.ctc_argc, args) < 0)
2802	  {
2803	    free (args);
2804	    goto err_input;
2805	  }
2806
2807	for (j = 0; j < fi.ctc_argc; j++)
2808	  {
2809	    args[j] = ctf_dedup_id_to_target (output, target, inputs, ninputs,
2810					      parents, input, input_num,
2811					      args[j]);
2812	    if (args[j] == CTF_ERR)
2813	      goto err_input;
2814	  }
2815
2816	if ((new_type = ctf_add_function (target, isroot,
2817					  &fi, args)) == CTF_ERR)
2818	  {
2819	    free (args);
2820	    goto err_target;
2821	  }
2822	free (args);
2823	break;
2824      }
2825
2826    case CTF_K_STRUCT:
2827    case CTF_K_UNION:
2828      {
2829	size_t size = ctf_type_size (input, type);
2830	void *out_id;
2831	/* Insert the structure itself, so other types can refer to it.  */
2832
2833	errtype = _("structure/union");
2834	if (kind == CTF_K_STRUCT)
2835	  new_type = ctf_add_struct_sized (target, isroot, name, size);
2836	else
2837	  new_type = ctf_add_union_sized (target, isroot, name, size);
2838
2839	if (new_type == CTF_ERR)
2840	  goto err_target;
2841
2842	out_id = CTF_DEDUP_GID (output, output_num, new_type);
2843	ctf_dprintf ("%i: Noting need to emit members of %p -> %p\n", depth,
2844		     id, out_id);
2845	/* Record the need to emit the members of this structure later.  */
2846	if (ctf_dynhash_insert (d->cd_emission_struct_members, id, out_id) < 0)
2847	  goto err_target;
2848	break;
2849      }
2850    default:
2851      ctf_err_warn (output, 0, ECTF_CORRUPT, _("%s: unknown type kind for "
2852					       "input type %lx"),
2853		    ctf_link_input_name (input), type);
2854      return ctf_set_errno (output, ECTF_CORRUPT);
2855    }
2856
2857  if (!emission_hashed
2858      && new_type != 0
2859      && ctf_dynhash_cinsert (target->ctf_dedup.cd_output_emission_hashes,
2860			      hval, (void *) (uintptr_t) new_type) < 0)
2861    {
2862      ctf_err_warn (output, 0, ENOMEM, _("out of memory tracking deduplicated "
2863					 "global type IDs"));
2864	return ctf_set_errno (output, ENOMEM);
2865    }
2866
2867  if (!emission_hashed && new_type != 0)
2868    ctf_dprintf ("%i: Inserted %s, %i/%lx -> %lx into emission hash for "
2869		 "target %p (%s)\n", depth, hval, input_num, type, new_type,
2870		 (void *) target, ctf_link_input_name (target));
2871
2872  return 0;
2873
2874 oom_hash:
2875  ctf_err_warn (output, 0, ENOMEM, _("out of memory creating emission-tracking "
2876				     "hashes"));
2877  return ctf_set_errno (output, ENOMEM);
2878
2879 err_input:
2880  ctf_err_warn (output, 0, ctf_errno (input),
2881		_("%s (%i): while emitting deduplicated %s, error getting "
2882		  "input type %lx"), ctf_link_input_name (input),
2883		input_num, errtype, type);
2884  return ctf_set_errno (output, ctf_errno (input));
2885 err_target:
2886  ctf_err_warn (output, 0, ctf_errno (target),
2887		_("%s (%i): while emitting deduplicated %s, error emitting "
2888		  "target type from input type %lx"),
2889		ctf_link_input_name (input), input_num,
2890		errtype, type);
2891  return ctf_set_errno (output, ctf_errno (target));
2892}
2893
2894/* Traverse the cd_emission_struct_members and emit the members of all
2895   structures and unions.  All other types are emitted and complete by this
2896   point.  */
2897
2898static int
2899ctf_dedup_emit_struct_members (ctf_file_t *output, ctf_file_t **inputs,
2900			       uint32_t ninputs, uint32_t *parents)
2901{
2902  ctf_dedup_t *d = &output->ctf_dedup;
2903  ctf_next_t *i = NULL;
2904  void *input_id, *target_id;
2905  int err;
2906  ctf_file_t *err_fp, *input_fp;
2907  int input_num;
2908  ctf_id_t err_type;
2909
2910  while ((err = ctf_dynhash_next (d->cd_emission_struct_members, &i,
2911				  &input_id, &target_id)) == 0)
2912    {
2913      ctf_next_t *j = NULL;
2914      ctf_file_t *target;
2915      uint32_t target_num;
2916      ctf_id_t input_type, target_type;
2917      ssize_t offset;
2918      ctf_id_t membtype;
2919      const char *name;
2920
2921      input_num = CTF_DEDUP_GID_TO_INPUT (input_id);
2922      input_fp = inputs[input_num];
2923      input_type = CTF_DEDUP_GID_TO_TYPE (input_id);
2924
2925      /* The output is either -1 (for the shared, parent output dict) or the
2926	 number of the corresponding input.  */
2927      target_num = CTF_DEDUP_GID_TO_INPUT (target_id);
2928      if (target_num == (uint32_t) -1)
2929	target = output;
2930      else
2931	{
2932	  target = inputs[target_num]->ctf_dedup.cd_output;
2933	  if (!ctf_assert (output, target))
2934	    {
2935	      err_fp = output;
2936	      err_type = input_type;
2937	      goto err_target;
2938	    }
2939	}
2940      target_type = CTF_DEDUP_GID_TO_TYPE (target_id);
2941
2942      while ((offset = ctf_member_next (input_fp, input_type, &j, &name,
2943					&membtype)) >= 0)
2944	{
2945	  err_fp = target;
2946	  err_type = target_type;
2947	  if ((membtype = ctf_dedup_id_to_target (output, target, inputs,
2948						  ninputs, parents, input_fp,
2949						  input_num,
2950						  membtype)) == CTF_ERR)
2951	    {
2952	      ctf_next_destroy (j);
2953	      goto err_target;
2954	    }
2955
2956	  if (name == NULL)
2957	    name = "";
2958#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
2959	  ctf_dprintf ("Emitting %s, offset %zi\n", name, offset);
2960#endif
2961	  if (ctf_add_member_offset (target, target_type, name,
2962				     membtype, offset) < 0)
2963	    {
2964	      ctf_next_destroy (j);
2965	      goto err_target;
2966	    }
2967	}
2968      if (ctf_errno (input_fp) != ECTF_NEXT_END)
2969	{
2970	  err = ctf_errno (input_fp);
2971	  ctf_next_destroy (i);
2972	  goto iterr;
2973	}
2974    }
2975  if (err != ECTF_NEXT_END)
2976    goto iterr;
2977
2978  return 0;
2979 err_target:
2980  ctf_next_destroy (i);
2981  ctf_err_warn (output, 0, ctf_errno (err_fp),
2982		_("%s (%i): error emitting members for structure type %lx"),
2983		ctf_link_input_name (input_fp), input_num, err_type);
2984  return ctf_set_errno (output, ctf_errno (err_fp));
2985 iterr:
2986  ctf_err_warn (output, 0, err, _("iteration failure emitting "
2987				  "structure members"));
2988  return ctf_set_errno (output, err);
2989}
2990
2991/* Populate the type mapping used by the types in one FP (which must be an input
2992   dict containing a non-null cd_output resulting from a ctf_dedup_emit_type
2993   walk).  */
2994static int
2995ctf_dedup_populate_type_mapping (ctf_file_t *shared, ctf_file_t *fp,
2996				 ctf_file_t **inputs)
2997{
2998  ctf_dedup_t *d = &shared->ctf_dedup;
2999  ctf_file_t *output = fp->ctf_dedup.cd_output;
3000  const void *k, *v;
3001  ctf_next_t *i = NULL;
3002  int err;
3003
3004  /* The shared dict (the output) stores its types in the fp itself, not in a
3005     separate cd_output dict.  */
3006  if (shared == fp)
3007    output = fp;
3008
3009  /* There may be no types to emit at all, or all the types in this TU may be
3010     shared.  */
3011  if (!output || !output->ctf_dedup.cd_output_emission_hashes)
3012    return 0;
3013
3014  while ((err = ctf_dynhash_cnext (output->ctf_dedup.cd_output_emission_hashes,
3015				  &i, &k, &v)) == 0)
3016    {
3017      const char *hval = (const char *) k;
3018      ctf_id_t id_out = (ctf_id_t) (uintptr_t) v;
3019      ctf_next_t *j = NULL;
3020      ctf_dynset_t *type_ids;
3021      const void *id;
3022
3023      type_ids = ctf_dynhash_lookup (d->cd_output_mapping, hval);
3024      if (!ctf_assert (shared, type_ids))
3025	return -1;
3026#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
3027      ctf_dprintf ("Traversing emission hash: hval %s\n", hval);
3028#endif
3029
3030      while ((err = ctf_dynset_cnext (type_ids, &j, &id)) == 0)
3031	{
3032	  ctf_file_t *input = inputs[CTF_DEDUP_GID_TO_INPUT (id)];
3033	  ctf_id_t id_in = CTF_DEDUP_GID_TO_TYPE (id);
3034
3035#ifdef ENABLE_LIBCTF_HASH_DEBUGGING
3036	  ctf_dprintf ("Adding mapping from %i/%lx to %lx\n",
3037		       CTF_DEDUP_GID_TO_INPUT (id), id_in, id_out);
3038#endif
3039	  ctf_add_type_mapping (input, id_in, output, id_out);
3040	}
3041      if (err != ECTF_NEXT_END)
3042	{
3043	  ctf_next_destroy (i);
3044	  goto err;
3045	}
3046    }
3047  if (err != ECTF_NEXT_END)
3048    goto err;
3049
3050  return 0;
3051
3052 err:
3053  ctf_err_warn (shared, 0, err, _("iteration error populating the type mapping"));
3054  return ctf_set_errno (shared, err);
3055}
3056
3057/* Populate the type mapping machinery used by the rest of the linker,
3058   by ctf_add_type, etc.  */
3059static int
3060ctf_dedup_populate_type_mappings (ctf_file_t *output, ctf_file_t **inputs,
3061				  uint32_t ninputs)
3062{
3063  size_t i;
3064
3065  if (ctf_dedup_populate_type_mapping (output, output, inputs) < 0)
3066    {
3067      ctf_err_warn (output, 0, 0, _("cannot populate type mappings for shared "
3068				    "CTF dict"));
3069      return -1;				/* errno is set for us.  */
3070    }
3071
3072  for (i = 0; i < ninputs; i++)
3073    {
3074      if (ctf_dedup_populate_type_mapping (output, inputs[i], inputs) < 0)
3075	{
3076	  ctf_err_warn (output, 0, ctf_errno (inputs[i]),
3077			_("cannot populate type mappings for per-CU CTF dict"));
3078	  return ctf_set_errno (output, ctf_errno (inputs[i]));
3079	}
3080    }
3081
3082  return 0;
3083}
3084
3085/* Emit deduplicated types into the outputs.  The shared type repository is
3086   OUTPUT, on which the ctf_dedup function must have already been called.  The
3087   PARENTS array contains the INPUTS index of the parent dict for every child
3088   dict at the corresponding index in the INPUTS (for non-child dicts, the value
3089   is undefined).
3090
3091   Return an array of fps with content emitted into them (starting with OUTPUT,
3092   which is the parent of all others, then all the newly-generated outputs).
3093
3094   If CU_MAPPED is set, this is a first pass for a link with a non-empty CU
3095   mapping: only one output will result.  */
3096
3097ctf_file_t **
3098ctf_dedup_emit (ctf_file_t *output, ctf_file_t **inputs, uint32_t ninputs,
3099		uint32_t *parents, uint32_t *noutputs, int cu_mapped)
3100{
3101  size_t num_outputs = 1;		/* Always at least one output: us.  */
3102  ctf_file_t **outputs;
3103  ctf_file_t **walk;
3104  size_t i;
3105
3106  ctf_dprintf ("Triggering emission.\n");
3107  if (ctf_dedup_walk_output_mapping (output, inputs, ninputs, parents,
3108				     ctf_dedup_emit_type, &cu_mapped) < 0)
3109    return NULL;				/* errno is set for us.  */
3110
3111  ctf_dprintf ("Populating struct members.\n");
3112  if (ctf_dedup_emit_struct_members (output, inputs, ninputs, parents) < 0)
3113    return NULL;				/* errno is set for us.  */
3114
3115  if (ctf_dedup_populate_type_mappings (output, inputs, ninputs) < 0)
3116    return NULL;				/* errno is set for us.  */
3117
3118  for (i = 0; i < ninputs; i++)
3119    {
3120      if (inputs[i]->ctf_dedup.cd_output)
3121	num_outputs++;
3122    }
3123
3124  if (!ctf_assert (output, !cu_mapped || (cu_mapped && num_outputs == 1)))
3125    return NULL;
3126
3127  if ((outputs = calloc (num_outputs, sizeof (ctf_file_t *))) == NULL)
3128    {
3129      ctf_err_warn (output, 0, ENOMEM,
3130		    _("out of memory allocating link outputs array"));
3131      ctf_set_errno (output, ENOMEM);
3132      return NULL;
3133    }
3134  *noutputs = num_outputs;
3135
3136  walk = outputs;
3137  *walk = output;
3138  output->ctf_refcnt++;
3139  walk++;
3140
3141  for (i = 0; i < ninputs; i++)
3142    {
3143      if (inputs[i]->ctf_dedup.cd_output)
3144	{
3145	  *walk = inputs[i]->ctf_dedup.cd_output;
3146	  inputs[i]->ctf_dedup.cd_output = NULL;
3147	  walk++;
3148	}
3149    }
3150
3151  ctf_dedup_fini (output, outputs, num_outputs);
3152  return outputs;
3153}
3154