1 /* CTF type deduplication.
2 Copyright (C) 2019-2025 Free Software Foundation, Inc.
4 This file is part of libctf.
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
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.
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/>. */
26 /* (In the below, relevant functions are named in square brackets.) */
28 /* Type deduplication is a three-phase process:
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).
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.
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
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_dict_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
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.
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.
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
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).
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
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
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
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.
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
152 2) COLLISIONAL MARKING.
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.
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.
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
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
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.
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.
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.
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
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.
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. */
260 /* Possible future optimizations are flagged with 'optimization opportunity'
263 /* Global optimization opportunity: a GC pass, eliminating types with no direct
264 or indirect citations from the other sections in the dictionary. */
266 /* Internal flag values for ctf_dedup_hash_type. */
268 /* Child call: consider forwardable types equivalent to forwards or stubs below
270 #define CTF_DEDUP_HASH_INTERNAL_CHILD 0x01
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.
275 On 32-bit platforms, we pack things together differently: see the note
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)
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))
290 #ifdef IDS_NEED_ALLOCATION
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. */
297 id_to_packed_id (ctf_dict_t
*fp
, int input_num
, ctf_id_t type
)
300 ctf_type_id_key_t
*dynkey
= NULL
;
301 ctf_type_id_key_t key
= { input_num
, type
};
303 if (!ctf_dynhash_lookup_kv (fp
->ctf_dedup
.cd_id_to_dict_t
,
304 &key
, &lookup
, NULL
))
306 if ((dynkey
= malloc (sizeof (ctf_type_id_key_t
))) == NULL
)
308 memcpy (dynkey
, &key
, sizeof (ctf_type_id_key_t
));
310 if (ctf_dynhash_insert (fp
->ctf_dedup
.cd_id_to_dict_t
, dynkey
, NULL
) < 0)
313 ctf_dynhash_lookup_kv (fp
->ctf_dedup
.cd_id_to_dict_t
,
314 dynkey
, &lookup
, NULL
);
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. */
320 return (void *) lookup
;
324 ctf_set_errno (fp
, ENOMEM
);
329 packed_id_to_input (const void *id
)
331 const ctf_type_id_key_t
*key
= (ctf_type_id_key_t
*) id
;
333 return key
->ctii_input_num
;
337 packed_id_to_type (const void *id
)
339 const ctf_type_id_key_t
*key
= (ctf_type_id_key_t
*) id
;
341 return key
->ctii_type
;
345 /* Make an element in a dynhash-of-dynsets, or return it if already present. */
347 static ctf_dynset_t
*
348 make_set_element (ctf_dynhash_t
*set
, const void *key
)
350 ctf_dynset_t
*element
;
352 if ((element
= ctf_dynhash_lookup (set
, key
)) == NULL
)
354 if ((element
= ctf_dynset_create (htab_hash_string
,
359 if (ctf_dynhash_insert (set
, (void *) key
, element
) < 0)
361 ctf_dynset_destroy (element
);
369 /* Initialize the dedup atoms table. */
371 ctf_dedup_atoms_init (ctf_dict_t
*fp
)
373 if (fp
->ctf_dedup_atoms
)
376 if (!fp
->ctf_dedup_atoms_alloc
)
378 if ((fp
->ctf_dedup_atoms_alloc
379 = ctf_dynset_create (htab_hash_string
, htab_eq_string
,
381 return ctf_set_errno (fp
, ENOMEM
);
383 fp
->ctf_dedup_atoms
= fp
->ctf_dedup_atoms_alloc
;
387 /* Intern things in the dedup atoms table. */
390 intern (ctf_dict_t
*fp
, char *atom
)
397 if (!ctf_dynset_exists (fp
->ctf_dedup_atoms
, atom
, &foo
))
399 if (ctf_dynset_insert (fp
->ctf_dedup_atoms
, atom
) < 0)
401 ctf_set_errno (fp
, ENOMEM
);
409 return (const char *) foo
;
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 pointer into the cd_decorated_names atoms table. */
417 ctf_decorate_type_name (ctf_dict_t
*fp
, const char *name
, int kind
)
419 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
444 if ((ret
= ctf_dynhash_lookup (d
->cd_decorated_names
[i
], name
)) == NULL
)
448 if ((str
= malloc (strlen (name
) + strlen (k
) + 1)) == NULL
)
453 ret
= intern (fp
, str
);
457 if (ctf_dynhash_cinsert (d
->cd_decorated_names
[i
], name
, ret
) < 0)
464 ctf_set_errno (fp
, ENOMEM
);
468 /* Hash a type, possibly debugging-dumping something about it as well. */
470 ctf_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_
)
474 ctf_sha1_add (sha1
, buf
, len
);
476 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
478 char tmp_hval
[CTF_SHA1_SIZE
];
480 ctf_sha1_fini (&tmp
, tmp_hval
);
481 ctf_dprintf ("%lu: after hash addition of %s: %s\n", depth
, description
,
487 ctf_dedup_hash_type (ctf_dict_t
*fp
, ctf_dict_t
*input
,
488 ctf_dict_t
**inputs
, int input_num
,
489 ctf_id_t type
, int flags
, unsigned long depth
,
490 int (*populate_fun
) (ctf_dict_t
*fp
,
496 const char *decorated_name
,
499 /* Determine whether this type is being hashed as a stub (in which case it is
500 unsafe to cache it). */
502 ctf_dedup_is_stub (const char *name
, int kind
, int fwdkind
, int flags
)
504 /* We can cache all types unless we are recursing to children and are hashing
505 in a tagged struct, union or forward, all of which are replaced with their
506 decorated name as a stub and will have different hash values when hashed at
509 return ((flags
& CTF_DEDUP_HASH_INTERNAL_CHILD
) && name
510 && (kind
== CTF_K_STRUCT
|| kind
== CTF_K_UNION
511 || (kind
== CTF_K_FORWARD
&& (fwdkind
== CTF_K_STRUCT
512 || fwdkind
== CTF_K_UNION
))));
515 /* Populate struct_origin if need be (not already populated, or populated with
516 a different origin), in which case it must go to -1, "shared".)
518 Only called for forwards or forwardable types with names, when the link mode
519 is CTF_LINK_SHARE_DUPLICATED. */
521 ctf_dedup_record_origin (ctf_dict_t
*fp
, int input_num
, const char *decorated
,
524 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
526 int populate_origin
= 0;
528 if (ctf_dynhash_lookup_kv (d
->cd_struct_origin
, decorated
, NULL
, &origin
))
530 if (CTF_DEDUP_GID_TO_INPUT (origin
) != input_num
531 && CTF_DEDUP_GID_TO_INPUT (origin
) != -1)
534 origin
= CTF_DEDUP_GID (fp
, -1, -1);
544 if (ctf_dynhash_cinsert (d
->cd_struct_origin
, decorated
, origin
) < 0)
545 return ctf_set_errno (fp
, errno
);
549 /* Do the underlying hashing and recursion for ctf_dedup_hash_type (which it
550 calls, recursively). */
553 ctf_dedup_rhash_type (ctf_dict_t
*fp
, ctf_dict_t
*input
, ctf_dict_t
**inputs
,
554 int input_num
, ctf_id_t type
, void *type_id
,
555 const ctf_type_t
*tp
, const char *name
,
556 const char *decorated
, int kind
, int flags
,
558 int (*populate_fun
) (ctf_dict_t
*fp
,
564 const char *decorated_name
,
567 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
568 ctf_next_t
*i
= NULL
;
571 char hashbuf
[CTF_SHA1_SIZE
];
572 const char *hval
= NULL
;
576 const char *citer
= NULL
;
577 ctf_dynset_t
*citers
= NULL
;
579 /* Add a citer to the citers set. */
580 #define ADD_CITER(citers, hval) \
583 whaterr = N_("error updating citers"); \
585 if ((citers = ctf_dynset_create (htab_hash_string, \
589 if (ctf_dynset_cinsert (citers, hval) < 0) \
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. */
599 if (ctf_dedup_is_stub (name
, kind
, tp
->ctt_type
, flags
))
601 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
602 ctf_dprintf ("Struct/union/forward citation: substituting forwarding "
603 "stub with decorated name %s\n", decorated
);
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
);
611 if ((hval
= intern (fp
, strdup (hashbuf
))) == NULL
)
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. */
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. */
629 /* Now ensure that subsequent recursive calls (but *not* the top-level call)
630 get this treatment. */
631 flags
|= CTF_DEDUP_HASH_INTERNAL_CHILD
;
633 /* If this is a struct, union, or forward with a name, record the unique
634 originating input TU, if there is one. */
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. */
641 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
642 ctf_dprintf ("%lu: hashing thing with ID %i/%lx (kind %i): %s.\n",
643 depth
, input_num
, type
, kind
, name
? name
: "");
646 /* Some type kinds don't have names: the API provides no way to set the name,
647 so the type the deduplicator outputs will be nameless even if the input
648 somehow has a name, and the name should not be mixed into the hash. */
662 /* Mix in invariant stuff, transforming the type kind if needed. Note that
663 the vlen is *not* hashed in: the actual variable-length info is hashed in
664 instead, piecewise. The vlen is not part of the type, only the
665 variable-length data is: identical types with distinct vlens are quite
666 possible. Equally, we do not want to hash in the isroot flag: both the
667 compiler and the deduplicator set the nonroot flag to indicate clashes with
668 *other types in the same TU* with the same name: so two types can easily
669 have distinct nonroot flags, yet be exactly the same type.*/
671 ctf_sha1_init (&hash
);
673 ctf_dedup_sha1_add (&hash
, name
, strlen (name
) + 1, "name", depth
);
674 ctf_dedup_sha1_add (&hash
, &kind
, sizeof (uint32_t), "kind", depth
);
676 /* Hash content of this type. */
680 /* No extra state. */
684 /* Add the forwarded kind, stored in the ctt_type. */
685 ctf_dedup_sha1_add (&hash
, &tp
->ctt_type
, sizeof (tp
->ctt_type
),
686 "forwarded kind", depth
);
692 memset (&ep
, 0, sizeof (ctf_encoding_t
));
694 ctf_dedup_sha1_add (&hash
, &tp
->ctt_size
, sizeof (uint32_t), "size",
696 if (ctf_type_encoding (input
, type
, &ep
) < 0)
698 whaterr
= N_("error getting encoding");
701 ctf_dedup_sha1_add (&hash
, &ep
, sizeof (ctf_encoding_t
), "encoding",
705 /* Types that reference other types. */
711 /* Hash the referenced type, if not already hashed, and mix it in. */
712 child_type
= ctf_type_reference (input
, type
);
713 if ((hval
= ctf_dedup_hash_type (fp
, input
, inputs
, input_num
, child_type
,
714 flags
, depth
, populate_fun
)) == NULL
)
716 whaterr
= N_("error doing referenced type hashing");
719 ctf_dedup_sha1_add (&hash
, hval
, strlen (hval
) + 1, "referenced type",
725 /* The slices of two types hash identically only if the type they overlay
726 also has the same encoding. This is not ideal, but in practice will work
727 well enough. We work directly rather than using the CTF API because
728 we do not want the slice's normal automatically-shine-through
729 semantics to kick in here. */
732 const ctf_slice_t
*slice
;
733 const ctf_dtdef_t
*dtd
;
737 child_type
= ctf_type_reference (input
, type
);
738 ctf_get_ctt_size (input
, tp
, &size
, &increment
);
739 ctf_dedup_sha1_add (&hash
, &size
, sizeof (ssize_t
), "size", depth
);
741 if ((hval
= ctf_dedup_hash_type (fp
, input
, inputs
, input_num
,
742 child_type
, flags
, depth
,
743 populate_fun
)) == NULL
)
745 whaterr
= N_("error doing slice-referenced type hashing");
748 ctf_dedup_sha1_add (&hash
, hval
, strlen (hval
) + 1, "sliced type",
752 if ((dtd
= ctf_dynamic_type (input
, type
)) != NULL
)
753 slice
= (ctf_slice_t
*) dtd
->dtd_vlen
;
755 slice
= (ctf_slice_t
*) ((uintptr_t) tp
+ increment
);
757 ctf_dedup_sha1_add (&hash
, &slice
->cts_offset
,
758 sizeof (slice
->cts_offset
), "slice offset", depth
);
759 ctf_dedup_sha1_add (&hash
, &slice
->cts_bits
,
760 sizeof (slice
->cts_bits
), "slice bits", depth
);
768 if (ctf_array_info (input
, type
, &ar
) < 0)
770 whaterr
= N_("error getting array info");
774 if ((hval
= ctf_dedup_hash_type (fp
, input
, inputs
, input_num
,
775 ar
.ctr_contents
, flags
, depth
,
776 populate_fun
)) == NULL
)
778 whaterr
= N_("error doing array contents type hashing");
781 ctf_dedup_sha1_add (&hash
, hval
, strlen (hval
) + 1, "array contents",
783 ADD_CITER (citers
, hval
);
785 if ((hval
= ctf_dedup_hash_type (fp
, input
, inputs
, input_num
,
786 ar
.ctr_index
, flags
, depth
,
787 populate_fun
)) == NULL
)
789 whaterr
= N_("error doing array index type hashing");
792 ctf_dedup_sha1_add (&hash
, hval
, strlen (hval
) + 1, "array index",
794 ctf_dedup_sha1_add (&hash
, &ar
.ctr_nelems
, sizeof (ar
.ctr_nelems
),
795 "element count", depth
);
796 ADD_CITER (citers
, hval
);
806 if (ctf_func_type_info (input
, type
, &fi
) < 0)
808 whaterr
= N_("error getting func type info");
812 if ((hval
= ctf_dedup_hash_type (fp
, input
, inputs
, input_num
,
813 fi
.ctc_return
, flags
, depth
,
814 populate_fun
)) == NULL
)
816 whaterr
= N_("error getting func return type");
819 ctf_dedup_sha1_add (&hash
, hval
, strlen (hval
) + 1, "func return",
821 ctf_dedup_sha1_add (&hash
, &fi
.ctc_argc
, sizeof (fi
.ctc_argc
),
823 ctf_dedup_sha1_add (&hash
, &fi
.ctc_flags
, sizeof (fi
.ctc_flags
),
824 "func flags", depth
);
825 ADD_CITER (citers
, hval
);
827 if ((args
= calloc (fi
.ctc_argc
, sizeof (ctf_id_t
))) == NULL
)
830 whaterr
= N_("error doing memory allocation");
834 if (ctf_func_type_args (input
, type
, fi
.ctc_argc
, args
) < 0)
837 whaterr
= N_("error getting func arg type");
840 for (j
= 0; j
< fi
.ctc_argc
; j
++)
842 if ((hval
= ctf_dedup_hash_type (fp
, input
, inputs
, input_num
,
843 args
[j
], flags
, depth
,
844 populate_fun
)) == NULL
)
847 whaterr
= N_("error doing func arg type hashing");
850 ctf_dedup_sha1_add (&hash
, hval
, strlen (hval
) + 1, "func arg type",
852 ADD_CITER (citers
, hval
);
862 ctf_dedup_sha1_add (&hash
, &tp
->ctt_size
, sizeof (uint32_t),
864 while ((ename
= ctf_enum_next (input
, type
, &i
, &val
)) != NULL
)
866 ctf_dedup_sha1_add (&hash
, ename
, strlen (ename
) + 1, "enumerator",
868 ctf_dedup_sha1_add (&hash
, &val
, sizeof (val
), "enumerand", depth
);
870 if (ctf_errno (input
) != ECTF_NEXT_END
)
872 whaterr
= N_("error doing enum member iteration");
877 /* Top-level only. */
886 ctf_get_ctt_size (input
, tp
, &size
, NULL
);
887 ctf_dedup_sha1_add (&hash
, &size
, sizeof (ssize_t
), "struct size",
890 while ((offset
= ctf_member_next (input
, type
, &i
, &mname
, &membtype
,
895 ctf_dedup_sha1_add (&hash
, mname
, strlen (mname
) + 1,
896 "member name", depth
);
898 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
899 ctf_dprintf ("%lu: Traversing to member %s\n", depth
, mname
);
901 if ((hval
= ctf_dedup_hash_type (fp
, input
, inputs
, input_num
,
902 membtype
, flags
, depth
,
903 populate_fun
)) == NULL
)
905 whaterr
= N_("error doing struct/union member type hashing");
909 ctf_dedup_sha1_add (&hash
, hval
, strlen (hval
) + 1, "member hash",
911 ctf_dedup_sha1_add (&hash
, &offset
, sizeof (offset
), "member offset",
913 ADD_CITER (citers
, hval
);
915 if (ctf_errno (input
) != ECTF_NEXT_END
)
917 whaterr
= N_("error doing struct/union member iteration");
923 whaterr
= N_("error: unknown type kind");
926 ctf_sha1_fini (&hash
, hashbuf
);
928 if ((hval
= intern (fp
, strdup (hashbuf
))) == NULL
)
930 whaterr
= N_("cannot intern hash");
934 /* Populate the citers for this type's subtypes, now the hash for the type
936 whaterr
= N_("error tracking citers");
940 ctf_dynset_t
*citer_hashes
;
942 if ((citer_hashes
= make_set_element (d
->cd_citers
, citer
)) == NULL
)
944 if (ctf_dynset_cinsert (citer_hashes
, hval
) < 0)
951 while ((err
= ctf_dynset_cnext (citers
, &i
, &k
)) == 0)
953 ctf_dynset_t
*citer_hashes
;
954 citer
= (const char *) k
;
956 if ((citer_hashes
= make_set_element (d
->cd_citers
, citer
)) == NULL
)
959 if (ctf_dynset_exists (citer_hashes
, hval
, NULL
))
961 if (ctf_dynset_cinsert (citer_hashes
, hval
) < 0)
964 if (err
!= ECTF_NEXT_END
)
966 ctf_dynset_destroy (citers
);
972 ctf_next_destroy (i
);
974 err
= ctf_errno (input
);
976 ctf_sha1_fini (&hash
, NULL
);
977 ctf_err_warn (fp
, 0, err
, _("%s (%i): %s: during type hashing for type %lx, "
978 "kind %i"), ctf_link_input_name (input
),
979 input_num
, gettext (whaterr
), type
, kind
);
982 ctf_set_errno (fp
, errno
);
983 ctf_err_warn (fp
, 0, 0, _("%s (%i): %s: during type hashing for type %lx, "
984 "kind %i"), ctf_link_input_name (input
),
985 input_num
, gettext (whaterr
), type
, kind
);
989 /* Hash a TYPE in the INPUT: FP is the eventual output, where the ctf_dedup
990 state is stored. INPUT_NUM is the number of this input in the set of inputs.
991 Record its hash in FP's cd_type_hashes once it is known.
993 (The flags argument currently accepts only the flag
994 CTF_DEDUP_HASH_INTERNAL_CHILD, an implementation detail used to prevent
995 struct/union hashing in recursive traversals below the TYPE.)
997 We use the CTF API rather than direct access wherever possible, because types
998 that appear identical through the API should be considered identical, with
999 one exception: slices should only be considered identical to other slices,
1000 not to the corresponding unsliced type.
1002 The POPULATE_FUN is a mandatory hook that populates other mappings with each
1003 type we see (excepting types that are recursively hashed as stubs). The
1004 caller should not rely on the order of calls to this hook, though it will be
1005 called at least once for every non-stub reference to every type.
1007 Returns a hash value (an atom), or NULL on error. */
1010 ctf_dedup_hash_type (ctf_dict_t
*fp
, ctf_dict_t
*input
,
1011 ctf_dict_t
**inputs
, int input_num
, ctf_id_t type
,
1012 int flags
, unsigned long depth
,
1013 int (*populate_fun
) (ctf_dict_t
*fp
,
1015 ctf_dict_t
**inputs
,
1019 const char *decorated_name
,
1022 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
1023 const ctf_type_t
*tp
;
1025 const char *hval
= NULL
;
1027 const char *whaterr
;
1028 const char *decorated
= NULL
;
1029 uint32_t kind
, fwdkind
;
1033 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1034 ctf_dprintf ("%lu: ctf_dedup_hash_type (%i, %lx, flags %x)\n", depth
, input_num
, type
, flags
);
1037 /* The unimplemented type doesn't really exist, but must be noted in parent
1038 hashes: so it gets a fixed, arbitrary hash. */
1040 return "00000000000000000000";
1042 /* Possible optimization: if the input type is in the parent type space, just
1043 copy recursively-cited hashes from the parent's types into the output
1044 mapping rather than rehashing them. */
1046 type_id
= CTF_DEDUP_GID (fp
, input_num
, type
);
1048 if ((tp
= ctf_lookup_by_id (&input
, type
)) == NULL
)
1050 ctf_set_errno (fp
, ctf_errno (input
));
1051 ctf_err_warn (fp
, 0, 0, _("%s (%i): lookup failure for type %lx: "
1052 "flags %x"), ctf_link_input_name (input
),
1053 input_num
, type
, flags
);
1054 return NULL
; /* errno is set for us. */
1057 kind
= LCTF_INFO_KIND (input
, tp
->ctt_info
);
1058 name
= ctf_strraw (input
, tp
->ctt_name
);
1060 if (tp
->ctt_name
== 0 || !name
|| name
[0] == '\0')
1063 /* Decorate the name appropriately for the namespace it appears in: forwards
1064 appear in the namespace of their referent. */
1069 if (kind
== CTF_K_FORWARD
)
1070 fwdkind
= tp
->ctt_type
;
1072 if ((decorated
= ctf_decorate_type_name (fp
, name
, fwdkind
)) == NULL
)
1073 return NULL
; /* errno is set for us. */
1076 /* If not hashing a stub, we can rely on various sorts of caches.
1078 Optimization opportunity: we may be able to avoid calling the populate_fun
1081 if (!ctf_dedup_is_stub (name
, kind
, fwdkind
, flags
))
1083 if ((hval
= ctf_dynhash_lookup (d
->cd_type_hashes
, type_id
)) != NULL
)
1085 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1086 ctf_dprintf ("%lu: Known hash for ID %i/%lx: %s\n", depth
, input_num
,
1089 populate_fun (fp
, input
, inputs
, input_num
, type
, type_id
,
1096 /* We have never seen this type before, and must figure out its hash and the
1097 hashes of the types it cites.
1099 Hash this type, and call ourselves recursively. (The hashing part is
1100 optional, and is disabled if overidden_hval is set.) */
1102 if ((hval
= ctf_dedup_rhash_type (fp
, input
, inputs
, input_num
,
1103 type
, type_id
, tp
, name
, decorated
,
1104 kind
, flags
, depth
, populate_fun
)) == NULL
)
1105 return NULL
; /* errno is set for us. */
1107 /* The hash of this type is now known: record it unless caching is unsafe
1108 because the hash value will change later. This will be the final storage
1109 of this type's hash, so we call the population function on it. */
1111 if (!ctf_dedup_is_stub (name
, kind
, fwdkind
, flags
))
1113 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1114 ctf_dprintf ("Caching %lx, ID %p (%s), %s in final location\n", type
,
1115 type_id
, name
? name
: "", hval
);
1118 if (ctf_dynhash_cinsert (d
->cd_type_hashes
, type_id
, hval
) < 0)
1120 whaterr
= N_("error hash caching");
1124 if (populate_fun (fp
, input
, inputs
, input_num
, type
, type_id
,
1125 decorated
, hval
) < 0)
1127 whaterr
= N_("error calling population function");
1128 goto err
; /* errno is set for us. */
1132 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1133 ctf_dprintf ("%lu: Returning final hash for ID %i/%lx: %s\n", depth
,
1134 input_num
, type
, hval
);
1139 ctf_set_errno (fp
, errno
);
1141 ctf_err_warn (fp
, 0, 0, _("%s (%i): %s: during type hashing, "
1142 "type %lx, kind %i"),
1143 ctf_link_input_name (input
), input_num
,
1144 gettext (whaterr
), type
, kind
);
1149 ctf_dedup_count_name (ctf_dict_t
*fp
, const char *name
, void *id
);
1151 /* Populate a number of useful mappings not directly used by the hashing
1152 machinery: the output mapping, the cd_name_counts mapping from name -> hash
1153 -> count of hashval deduplication state for a given hashed type, and the
1154 cd_output_first_tu mapping. */
1157 ctf_dedup_populate_mappings (ctf_dict_t
*fp
, ctf_dict_t
*input _libctf_unused_
,
1158 ctf_dict_t
**inputs _libctf_unused_
,
1159 int input_num _libctf_unused_
,
1160 ctf_id_t type _libctf_unused_
, void *id
,
1161 const char *decorated_name
,
1164 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
1165 ctf_dynset_t
*type_ids
;
1167 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1168 ctf_dprintf ("Hash %s, %s, into output mapping for %i/%lx @ %s\n",
1169 hval
, decorated_name
? decorated_name
: "(unnamed)",
1170 input_num
, type
, ctf_link_input_name (input
));
1172 const char *orig_hval
;
1174 /* Make sure we never map a single GID to multiple hash values. */
1176 if ((orig_hval
= ctf_dynhash_lookup (d
->cd_output_mapping_guard
, id
)) != NULL
)
1178 /* We can rely on pointer identity here, since all hashes are
1180 if (!ctf_assert (fp
, orig_hval
== hval
))
1184 if (ctf_dynhash_cinsert (d
->cd_output_mapping_guard
, id
, hval
) < 0)
1185 return ctf_set_errno (fp
, errno
);
1188 /* Record the type in the output mapping: if this is the first time this type
1189 has been seen, also record it in the cd_output_first_gid. Because we
1190 traverse types in TU order and we do not merge types after the hashing
1191 phase, this will be the lowest TU this type ever appears in. */
1193 if ((type_ids
= ctf_dynhash_lookup (d
->cd_output_mapping
,
1196 if (ctf_dynhash_cinsert (d
->cd_output_first_gid
, hval
, id
) < 0)
1197 return ctf_set_errno (fp
, errno
);
1199 if ((type_ids
= ctf_dynset_create (htab_hash_pointer
,
1202 return ctf_set_errno (fp
, errno
);
1203 if (ctf_dynhash_insert (d
->cd_output_mapping
, (void *) hval
,
1206 ctf_dynset_destroy (type_ids
);
1207 return ctf_set_errno (fp
, errno
);
1210 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1212 /* Verify that all types with this hash are of the same kind, and that the
1213 first TU a type was seen in never falls. */
1217 ctf_next_t
*i
= NULL
;
1218 int orig_kind
= ctf_type_kind_unsliced (input
, type
);
1221 orig_first_tu
= CTF_DEDUP_GID_TO_INPUT
1222 (ctf_dynhash_lookup (d
->cd_output_first_gid
, hval
));
1223 if (!ctf_assert (fp
, orig_first_tu
<= CTF_DEDUP_GID_TO_INPUT (id
)))
1226 while ((err
= ctf_dynset_cnext (type_ids
, &i
, &one_id
)) == 0)
1228 ctf_dict_t
*foo
= inputs
[CTF_DEDUP_GID_TO_INPUT (one_id
)];
1229 ctf_id_t bar
= CTF_DEDUP_GID_TO_TYPE (one_id
);
1230 if (ctf_type_kind_unsliced (foo
, bar
) != orig_kind
)
1232 ctf_err_warn (fp
, 1, 0, "added wrong kind to output mapping "
1233 "for hash %s named %s: %p/%lx from %s is "
1234 "kind %i, but newly-added %p/%lx from %s is "
1236 decorated_name
? decorated_name
: "(unnamed)",
1238 ctf_link_input_name (foo
),
1239 ctf_type_kind_unsliced (foo
, bar
),
1240 (void *) input
, type
,
1241 ctf_link_input_name (input
), orig_kind
);
1242 if (!ctf_assert (fp
, ctf_type_kind_unsliced (foo
, bar
)
1247 if (err
!= ECTF_NEXT_END
)
1248 return ctf_set_errno (fp
, err
);
1252 /* This function will be repeatedly called for the same types many times:
1253 don't waste time reinserting the same keys in that case. */
1254 if (!ctf_dynset_exists (type_ids
, id
, NULL
)
1255 && ctf_dynset_insert (type_ids
, id
) < 0)
1256 return ctf_set_errno (fp
, errno
);
1258 if (ctf_type_kind_unsliced (input
, type
) == CTF_K_ENUM
)
1260 ctf_next_t
*i
= NULL
;
1261 const char *enumerator
;
1263 while ((enumerator
= ctf_enum_next (input
, type
, &i
, NULL
)) != NULL
)
1265 if (ctf_dedup_count_name (fp
, enumerator
, id
) < 0)
1267 ctf_next_destroy (i
);
1271 if (ctf_errno (input
) != ECTF_NEXT_END
)
1272 return ctf_set_errno (fp
, ctf_errno (input
));
1275 /* The rest only needs to happen for types with names. */
1276 if (!decorated_name
)
1279 if (ctf_dedup_count_name (fp
, decorated_name
, id
) < 0)
1280 return -1; /* errno is set for us. */
1286 ctf_dedup_count_name (ctf_dict_t
*fp
, const char *name
, void *id
)
1288 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
1289 ctf_dynhash_t
*name_counts
;
1293 /* Count the number of occurrences of the hash value for this GID. */
1295 hval
= ctf_dynhash_lookup (d
->cd_type_hashes
, id
);
1297 /* Mapping from name -> hash(hashval, count) not already present? */
1298 if ((name_counts
= ctf_dynhash_lookup (d
->cd_name_counts
, name
)) == NULL
)
1300 if ((name_counts
= ctf_dynhash_create (ctf_hash_string
,
1302 NULL
, NULL
)) == NULL
)
1303 return ctf_set_errno (fp
, errno
);
1304 if (ctf_dynhash_cinsert (d
->cd_name_counts
, name
, name_counts
) < 0)
1306 ctf_dynhash_destroy (name_counts
);
1307 return ctf_set_errno (fp
, errno
);
1311 /* This will, conveniently, return NULL (i.e. 0) for a new entry. */
1312 count
= (long int) (uintptr_t) ctf_dynhash_lookup (name_counts
, hval
);
1314 if (ctf_dynhash_cinsert (name_counts
, hval
,
1315 (const void *) (uintptr_t) (count
+ 1)) < 0)
1316 return ctf_set_errno (fp
, errno
);
1321 /* Mark a single hash as corresponding to a conflicting type. Mark all types
1322 that cite it as conflicting as well, terminating the recursive walk only when
1323 types that are already conflicted or types do not cite other types are seen.
1324 (Tagged structures and unions do not appear in the cd_citers graph, so the
1325 walk also terminates there, since any reference to a conflicting structure is
1326 just going to reference an unconflicting forward instead: see
1327 ctf_dedup_maybe_synthesize_forward.) */
1330 ctf_dedup_mark_conflicting_hash (ctf_dict_t
*fp
, const char *hval
)
1332 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
1333 ctf_next_t
*i
= NULL
;
1336 ctf_dynset_t
*citers
;
1338 /* Mark conflicted if not already so marked. */
1339 if (ctf_dynset_exists (d
->cd_conflicting_types
, hval
, NULL
))
1342 ctf_dprintf ("Marking %s as conflicted\n", hval
);
1344 if (ctf_dynset_cinsert (d
->cd_conflicting_types
, hval
) < 0)
1346 ctf_dprintf ("Out of memory marking %s as conflicted\n", hval
);
1347 return ctf_set_errno (fp
, errno
);
1350 /* If any types cite this type, mark them conflicted too. */
1351 if ((citers
= ctf_dynhash_lookup (d
->cd_citers
, hval
)) == NULL
)
1354 while ((err
= ctf_dynset_cnext (citers
, &i
, &k
)) == 0)
1356 const char *hv
= (const char *) k
;
1358 if (ctf_dynset_exists (d
->cd_conflicting_types
, hv
, NULL
))
1361 if (ctf_dedup_mark_conflicting_hash (fp
, hv
) < 0)
1363 ctf_next_destroy (i
);
1364 return -1; /* errno is set for us. */
1367 if (err
!= ECTF_NEXT_END
)
1368 return ctf_set_errno (fp
, err
);
1373 /* Look up a type kind from the output mapping, given a type hash value. */
1375 ctf_dedup_hash_kind (ctf_dict_t
*fp
, ctf_dict_t
**inputs
, const char *hash
)
1377 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
1379 ctf_dynset_t
*type_ids
;
1381 /* Precondition: the output mapping is populated. */
1382 if (!ctf_assert (fp
, ctf_dynhash_elements (d
->cd_output_mapping
) > 0))
1385 /* Look up some GID from the output hash for this type. (They are all
1386 identical, so we can pick any). Don't assert if someone calls this
1387 function wrongly, but do assert if the output mapping knows about the hash,
1388 but has nothing associated with it. */
1390 type_ids
= ctf_dynhash_lookup (d
->cd_output_mapping
, hash
);
1393 ctf_dprintf ("Looked up type kind by nonexistent hash %s.\n", hash
);
1394 return ctf_set_errno (fp
, ECTF_INTERNAL
);
1396 id
= ctf_dynset_lookup_any (type_ids
);
1397 if (!ctf_assert (fp
, id
))
1400 return ctf_type_kind_unsliced (inputs
[CTF_DEDUP_GID_TO_INPUT (id
)],
1401 CTF_DEDUP_GID_TO_TYPE (id
));
1404 /* Used to keep a count of types: i.e. distinct type hash values. */
1405 typedef struct ctf_dedup_type_counter
1408 ctf_dict_t
**inputs
;
1409 int num_non_forwards
;
1410 } ctf_dedup_type_counter_t
;
1412 /* Add to the type counter for one name entry from the cd_name_counts. */
1414 ctf_dedup_count_types (void *key_
, void *value _libctf_unused_
, void *arg_
)
1416 const char *hval
= (const char *) key_
;
1418 ctf_dedup_type_counter_t
*arg
= (ctf_dedup_type_counter_t
*) arg_
;
1420 kind
= ctf_dedup_hash_kind (arg
->fp
, arg
->inputs
, hval
);
1422 /* We rely on ctf_dedup_hash_kind setting the fp to -ECTF_INTERNAL on error to
1423 smuggle errors out of here. */
1425 if (kind
!= CTF_K_FORWARD
)
1427 arg
->num_non_forwards
++;
1428 ctf_dprintf ("Counting hash %s: kind %i: num_non_forwards is %i\n",
1429 hval
, kind
, arg
->num_non_forwards
);
1432 /* We only need to know if there is more than one non-forward (an ambiguous
1433 type): don't waste time iterating any more than needed to figure that
1436 if (arg
->num_non_forwards
> 1)
1442 /* Detect name ambiguity and mark ambiguous names as conflicting, other than the
1445 ctf_dedup_detect_name_ambiguity (ctf_dict_t
*fp
, ctf_dict_t
**inputs
)
1447 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
1448 ctf_next_t
*i
= NULL
;
1452 const char *whaterr
;
1454 /* Go through cd_name_counts for all CTF namespaces in turn. */
1456 while ((err
= ctf_dynhash_next (d
->cd_name_counts
, &i
, &k
, &v
)) == 0)
1458 const char *decorated
= (const char *) k
;
1459 ctf_dynhash_t
*name_counts
= (ctf_dynhash_t
*) v
;
1460 ctf_next_t
*j
= NULL
;
1462 /* If this is a forwardable kind or a forward (which we can tell without
1463 consulting the type because its decorated name has a space as its
1464 second character: see ctf_decorate_type_name), we are only interested
1465 in whether this name has many hashes associated with it: any such name
1466 is necessarily ambiguous, and types with that name are conflicting.
1467 Once we know whether this is true, we can skip to the next name: so use
1468 ctf_dynhash_iter_find for efficiency. */
1470 if (decorated
[0] != '\0' && decorated
[1] == ' ')
1472 ctf_dedup_type_counter_t counters
= { fp
, inputs
, 0 };
1474 ctf_dynhash_iter_find (name_counts
, ctf_dedup_count_types
, &counters
);
1476 /* Check for assertion failure and pass it up. */
1477 if (ctf_errno (fp
) == ECTF_INTERNAL
)
1480 if (counters
.num_non_forwards
> 1)
1484 while ((err
= ctf_dynhash_cnext (name_counts
, &j
, &hval_
, NULL
)) == 0)
1486 const char *hval
= (const char *) hval_
;
1487 ctf_dynset_t
*type_ids
;
1491 /* Dig through the types in this hash to find the non-forwards
1492 and mark them ambiguous. */
1494 type_ids
= ctf_dynhash_lookup (d
->cd_output_mapping
, hval
);
1496 /* Nonexistent? Must be a forward with no referent. */
1500 id
= ctf_dynset_lookup_any (type_ids
);
1502 kind
= ctf_type_kind (inputs
[CTF_DEDUP_GID_TO_INPUT (id
)],
1503 CTF_DEDUP_GID_TO_TYPE (id
));
1505 if (kind
!= CTF_K_FORWARD
)
1507 ctf_dprintf ("Marking %p, with hash %s, conflicting: one "
1508 "of many non-forward GIDs for %s\n", id
,
1510 ctf_dedup_mark_conflicting_hash (fp
, hval
);
1513 if (err
!= ECTF_NEXT_END
)
1515 whaterr
= N_("error marking conflicting structs/unions");
1522 /* This is an ordinary type. Find the most common type with this
1523 name, and mark it unconflicting: all others are conflicting. (We
1524 cannot do this sort of popularity contest with forwardable types
1525 because any forwards to that type would be immediately unified with
1526 the most-popular type on insertion, and we want conflicting structs
1527 et al to have all forwards left intact, so the user is notified
1528 that this type is conflicting. TODO: improve this in future by
1529 setting such forwards non-root-visible.)
1531 If multiple distinct types are "most common", pick the one that
1532 appears first on the link line, and within that, the one with the
1533 lowest type ID. (See sort_output_mapping.) */
1538 long max_hcount
= -1;
1539 void *max_gid
= NULL
;
1540 const char *max_hval
= NULL
;
1542 if (ctf_dynhash_elements (name_counts
) <= 1)
1545 /* First find the most common. */
1546 while ((err
= ctf_dynhash_cnext (name_counts
, &j
, &key
, &count
)) == 0)
1548 hval
= (const char *) key
;
1550 if ((long int) (uintptr_t) count
> max_hcount
)
1552 max_hcount
= (long int) (uintptr_t) count
;
1554 max_gid
= ctf_dynhash_lookup (d
->cd_output_first_gid
, hval
);
1556 else if ((long int) (uintptr_t) count
== max_hcount
)
1558 void *gid
= ctf_dynhash_lookup (d
->cd_output_first_gid
, hval
);
1560 if (CTF_DEDUP_GID_TO_INPUT(gid
) < CTF_DEDUP_GID_TO_INPUT(max_gid
)
1561 || (CTF_DEDUP_GID_TO_INPUT(gid
) == CTF_DEDUP_GID_TO_INPUT(max_gid
)
1562 && CTF_DEDUP_GID_TO_TYPE(gid
) < CTF_DEDUP_GID_TO_TYPE(max_gid
)))
1565 max_gid
= ctf_dynhash_lookup (d
->cd_output_first_gid
, hval
);
1569 if (err
!= ECTF_NEXT_END
)
1571 whaterr
= N_("error finding commonest conflicting type");
1575 /* Mark all the others as conflicting. */
1576 while ((err
= ctf_dynhash_cnext (name_counts
, &j
, &key
, NULL
)) == 0)
1578 hval
= (const char *) key
;
1579 if (strcmp (max_hval
, hval
) == 0)
1582 ctf_dprintf ("Marking %s, an uncommon hash for %s, conflicting\n",
1583 hval
, (const char *) k
);
1584 if (ctf_dedup_mark_conflicting_hash (fp
, hval
) < 0)
1586 whaterr
= N_("error marking hashes as conflicting");
1590 if (err
!= ECTF_NEXT_END
)
1592 whaterr
= N_("marking uncommon conflicting types");
1597 if (err
!= ECTF_NEXT_END
)
1599 whaterr
= N_("scanning for ambiguous names");
1606 ctf_next_destroy (i
);
1607 ctf_err_warn (fp
, 0, 0, "%s", gettext (whaterr
));
1608 return -1; /* errno is set for us. */
1611 ctf_err_warn (fp
, 0, err
, _("iteration failed: %s"), gettext (whaterr
));
1612 return ctf_set_errno (fp
, err
);
1615 ctf_next_destroy (i
);
1616 return -1; /* errno is set for us. */
1619 /* Initialize the deduplication machinery. */
1622 ctf_dedup_init (ctf_dict_t
*fp
)
1624 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
1627 if (ctf_dedup_atoms_init (fp
) < 0)
1630 #if IDS_NEED_ALLOCATION
1631 if ((d
->cd_id_to_dict_t
= ctf_dynhash_create (ctf_hash_type_id_key
,
1632 ctf_hash_eq_type_id_key
,
1633 free
, NULL
)) == NULL
)
1637 for (i
= 0; i
< 4; i
++)
1639 if ((d
->cd_decorated_names
[i
] = ctf_dynhash_create (ctf_hash_string
,
1641 NULL
, NULL
)) == NULL
)
1645 if ((d
->cd_name_counts
1646 = ctf_dynhash_create (ctf_hash_string
,
1647 ctf_hash_eq_string
, NULL
,
1648 (ctf_hash_free_fun
) ctf_dynhash_destroy
)) == NULL
)
1651 if ((d
->cd_type_hashes
1652 = ctf_dynhash_create (ctf_hash_integer
,
1653 ctf_hash_eq_integer
,
1654 NULL
, NULL
)) == NULL
)
1657 if ((d
->cd_struct_origin
1658 = ctf_dynhash_create (ctf_hash_string
,
1660 NULL
, NULL
)) == NULL
)
1664 = ctf_dynhash_create (ctf_hash_string
,
1665 ctf_hash_eq_string
, NULL
,
1666 (ctf_hash_free_fun
) ctf_dynset_destroy
)) == NULL
)
1669 if ((d
->cd_output_mapping
1670 = ctf_dynhash_create (ctf_hash_string
,
1671 ctf_hash_eq_string
, NULL
,
1672 (ctf_hash_free_fun
) ctf_dynset_destroy
)) == NULL
)
1675 if ((d
->cd_output_first_gid
1676 = ctf_dynhash_create (ctf_hash_string
,
1678 NULL
, NULL
)) == NULL
)
1681 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1682 if ((d
->cd_output_mapping_guard
1683 = ctf_dynhash_create (ctf_hash_integer
,
1684 ctf_hash_eq_integer
, NULL
, NULL
)) == NULL
)
1688 if ((d
->cd_input_nums
1689 = ctf_dynhash_create (ctf_hash_integer
,
1690 ctf_hash_eq_integer
,
1691 NULL
, NULL
)) == NULL
)
1694 if ((d
->cd_emission_struct_members
1695 = ctf_dynhash_create (ctf_hash_integer
,
1696 ctf_hash_eq_integer
,
1697 NULL
, NULL
)) == NULL
)
1700 if ((d
->cd_conflicting_types
1701 = ctf_dynset_create (htab_hash_string
,
1702 htab_eq_string
, NULL
)) == NULL
)
1708 ctf_err_warn (fp
, 0, ENOMEM
, _("ctf_dedup_init: cannot initialize: "
1710 return ctf_set_errno (fp
, ENOMEM
);
1713 /* No ctf_dedup calls are allowed after this call other than starting a new
1714 deduplication via ctf_dedup (not even ctf_dedup_type_mapping lookups). */
1716 ctf_dedup_fini (ctf_dict_t
*fp
, ctf_dict_t
**outputs
, uint32_t noutputs
)
1718 ctf_dedup_t
*d
= &fp
->ctf_dedup
;
1721 /* ctf_dedup_atoms is kept across links. */
1722 #if IDS_NEED_ALLOCATION
1723 ctf_dynhash_destroy (d
->cd_id_to_dict_t
);
1725 for (i
= 0; i
< 4; i
++)
1726 ctf_dynhash_destroy (d
->cd_decorated_names
[i
]);
1727 ctf_dynhash_destroy (d
->cd_name_counts
);
1728 ctf_dynhash_destroy (d
->cd_type_hashes
);
1729 ctf_dynhash_destroy (d
->cd_struct_origin
);
1730 ctf_dynhash_destroy (d
->cd_citers
);
1731 ctf_dynhash_destroy (d
->cd_output_mapping
);
1732 ctf_dynhash_destroy (d
->cd_output_first_gid
);
1733 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
1734 ctf_dynhash_destroy (d
->cd_output_mapping_guard
);
1736 ctf_dynhash_destroy (d
->cd_input_nums
);
1737 ctf_dynhash_destroy (d
->cd_emission_struct_members
);
1738 ctf_dynset_destroy (d
->cd_conflicting_types
);
1740 /* Free the per-output state. */
1743 for (i
= 0; i
< noutputs
; i
++)
1745 ctf_dedup_t
*od
= &outputs
[i
]->ctf_dedup
;
1746 ctf_dynhash_destroy (od
->cd_output_emission_hashes
);
1747 ctf_dynhash_destroy (od
->cd_output_emission_conflicted_forwards
);
1748 ctf_dict_close (od
->cd_output
);
1751 memset (d
, 0, sizeof (ctf_dedup_t
));
1754 /* Return 1 if this type is cited by multiple input dictionaries. */
1757 ctf_dedup_multiple_input_dicts (ctf_dict_t
*output
, ctf_dict_t
**inputs
,
1760 ctf_dedup_t
*d
= &output
->ctf_dedup
;
1761 ctf_dynset_t
*type_ids
;
1762 ctf_next_t
*i
= NULL
;
1764 ctf_dict_t
*found
= NULL
, *relative_found
= NULL
;
1765 const char *type_id
;
1766 ctf_dict_t
*input_fp
;
1769 const char *decorated
;
1774 type_ids
= ctf_dynhash_lookup (d
->cd_output_mapping
, hval
);
1775 if (!ctf_assert (output
, type_ids
))
1778 /* Scan across the IDs until we find proof that two disjoint dictionaries
1779 are referenced. Exit as soon as possible. Optimization opportunity, but
1780 possibly not worth it, given that this is only executed in
1781 CTF_LINK_SHARE_DUPLICATED mode. */
1783 while ((err
= ctf_dynset_next (type_ids
, &i
, &id
)) == 0)
1785 ctf_dict_t
*fp
= inputs
[CTF_DEDUP_GID_TO_INPUT (id
)];
1787 if (fp
== found
|| fp
== relative_found
)
1797 && (fp
->ctf_parent
== found
|| found
->ctf_parent
== fp
))
1799 relative_found
= fp
;
1804 ctf_next_destroy (i
);
1807 if ((err
!= ECTF_NEXT_END
) && (err
!= 0))
1809 ctf_err_warn (output
, 0, err
, _("iteration error "
1810 "propagating conflictedness"));
1811 return ctf_set_errno (output
, err
);
1817 /* This type itself does not appear in multiple input dicts: how about another
1818 related type with the same name (e.g. a forward if this is a struct,
1821 type_id
= ctf_dynset_lookup_any (type_ids
);
1822 if (!ctf_assert (output
, type_id
))
1825 input_fp
= inputs
[CTF_DEDUP_GID_TO_INPUT (type_id
)];
1826 input_id
= CTF_DEDUP_GID_TO_TYPE (type_id
);
1827 fwdkind
= ctf_type_kind_forwarded (input_fp
, input_id
);
1828 name
= ctf_type_name_raw (input_fp
, input_id
);
1830 if ((fwdkind
== CTF_K_STRUCT
|| fwdkind
== CTF_K_UNION
)
1835 if ((decorated
= ctf_decorate_type_name (output
, name
,
1837 return -1; /* errno is set for us. */
1839 origin
= ctf_dynhash_lookup (d
->cd_struct_origin
, decorated
);
1840 if ((origin
!= NULL
) && (CTF_DEDUP_GID_TO_INPUT (origin
) < 0))
1847 /* Demote unconflicting types which reference only one input, or which reference
1848 two inputs where one input is the parent of the other, into conflicting
1849 types. Only used if the link mode is CTF_LINK_SHARE_DUPLICATED. */
1852 ctf_dedup_conflictify_unshared (ctf_dict_t
*output
, ctf_dict_t
**inputs
)
1854 ctf_dedup_t
*d
= &output
->ctf_dedup
;
1855 ctf_next_t
*i
= NULL
;
1858 ctf_dynset_t
*to_mark
= NULL
;
1860 if ((to_mark
= ctf_dynset_create (htab_hash_string
, htab_eq_string
,
1864 while ((err
= ctf_dynhash_cnext (d
->cd_output_mapping
, &i
, &k
, NULL
)) == 0)
1866 const char *hval
= (const char *) k
;
1869 /* Types referenced by only one dict, with no type appearing under that
1870 name elsewhere, are marked conflicting. */
1872 conflicting
= !ctf_dedup_multiple_input_dicts (output
, inputs
, hval
);
1874 if (conflicting
< 0)
1875 goto err
; /* errno is set for us. */
1878 if (ctf_dynset_cinsert (to_mark
, hval
) < 0)
1881 if (err
!= ECTF_NEXT_END
)
1884 while ((err
= ctf_dynset_cnext (to_mark
, &i
, &k
)) == 0)
1886 const char *hval
= (const char *) k
;
1888 if (ctf_dedup_mark_conflicting_hash (output
, hval
) < 0)
1891 if (err
!= ECTF_NEXT_END
)
1894 ctf_dynset_destroy (to_mark
);
1899 ctf_set_errno (output
, errno
);
1901 err
= ctf_errno (output
);
1902 ctf_next_destroy (i
);
1904 ctf_dynset_destroy (to_mark
);
1905 ctf_err_warn (output
, 0, err
, _("conflictifying unshared types"));
1906 return ctf_set_errno (output
, err
);
1909 /* The core deduplicator. Populate cd_output_mapping in the output ctf_dedup with a
1910 mapping of all types that belong in this dictionary and where they come from, and
1911 cd_conflicting_types with an indication of whether each type is conflicted or not.
1912 OUTPUT is the top-level output: INPUTS is the array of input dicts; NINPUTS is the
1915 If CU_MAPPED is set, this is a first pass for a link with a non-empty CU
1916 mapping: only one output will result.
1918 Only deduplicates: does not emit the types into the output. Call
1919 ctf_dedup_emit afterwards to do that. */
1922 ctf_dedup (ctf_dict_t
*output
, ctf_dict_t
**inputs
, uint32_t ninputs
,
1925 ctf_dedup_t
*d
= &output
->ctf_dedup
;
1927 ctf_next_t
*it
= NULL
;
1929 if (ctf_dedup_init (output
) < 0)
1930 return -1; /* errno is set for us. */
1932 for (i
= 0; i
< ninputs
; i
++)
1934 ctf_dprintf ("Input %i: %s\n", (int) i
, ctf_link_input_name (inputs
[i
]));
1935 if (ctf_dynhash_insert (d
->cd_input_nums
, inputs
[i
],
1936 (void *) (uintptr_t) i
) < 0)
1938 ctf_set_errno (output
, errno
);
1939 ctf_err_warn (output
, 0, errno
, _("ctf_dedup: cannot initialize: %s\n"),
1940 ctf_errmsg (errno
));
1945 /* Some flags do not apply when CU-mapping: this is not a duplicated link,
1946 because there is only one output and we really don't want to end up marking
1947 all nonconflicting but appears-only-once types as conflicting (which in the
1948 CU-mapped link means we'd mark them all as non-root-visible!). */
1949 d
->cd_link_flags
= output
->ctf_link_flags
;
1951 d
->cd_link_flags
&= ~(CTF_LINK_SHARE_DUPLICATED
);
1953 /* Compute hash values for all types, recursively, treating child structures
1954 and unions equivalent to forwards, and hashing in the name of the referent
1955 of each such type into structures, unions, and non-opaque forwards.
1956 Populate a mapping from decorated name (including an indication of
1957 struct/union/enum namespace) to count of type hash values in
1958 cd_name_counts, a mapping from and a mapping from hash values to input type
1959 IDs in cd_output_mapping. */
1961 ctf_dprintf ("Computing type hashes\n");
1962 for (i
= 0; i
< ninputs
; i
++)
1966 while ((id
= ctf_type_next (inputs
[i
], &it
, NULL
, 1)) != CTF_ERR
)
1968 if (ctf_dedup_hash_type (output
, inputs
[i
], inputs
,
1970 ctf_dedup_populate_mappings
) == NULL
)
1971 goto err
; /* errno is set for us. */
1973 if (ctf_errno (inputs
[i
]) != ECTF_NEXT_END
)
1975 ctf_set_errno (output
, ctf_errno (inputs
[i
]));
1976 ctf_err_warn (output
, 0, 0, _("iteration failure "
1977 "computing type hashes"));
1982 /* Go through the cd_name_counts name->hash->count mapping for all CTF
1983 namespaces: any name with many hashes associated with it at this stage is
1984 necessarily ambiguous. Mark all the hashes except the most common as
1985 conflicting in the output. */
1987 ctf_dprintf ("Detecting type name ambiguity\n");
1988 if (ctf_dedup_detect_name_ambiguity (output
, inputs
) < 0)
1989 goto err
; /* errno is set for us. */
1991 /* If the link mode is CTF_LINK_SHARE_DUPLICATED, we change any unconflicting
1992 types whose output mapping references only one input dict into a
1993 conflicting type, so that they end up in the per-CU dictionaries. */
1995 if (d
->cd_link_flags
& CTF_LINK_SHARE_DUPLICATED
)
1997 ctf_dprintf ("Conflictifying unshared types\n");
1998 if (ctf_dedup_conflictify_unshared (output
, inputs
) < 0)
1999 goto err
; /* errno is set for us. */
2004 ctf_dedup_fini (output
, NULL
, 0);
2009 ctf_dedup_rwalk_output_mapping (ctf_dict_t
*output
, ctf_dict_t
**inputs
,
2010 uint32_t ninputs
, uint32_t *parents
,
2011 ctf_dynset_t
*already_visited
,
2013 int (*visit_fun
) (const char *hval
,
2015 ctf_dict_t
**inputs
,
2018 int already_visited
,
2024 void *arg
, unsigned long depth
);
2026 /* Like ctf_dedup_rwalk_output_mapping (which see), only takes a single target
2027 type and visits it. */
2029 ctf_dedup_rwalk_one_output_mapping (ctf_dict_t
*output
,
2030 ctf_dict_t
**inputs
, uint32_t ninputs
,
2032 ctf_dynset_t
*already_visited
,
2033 int visited
, void *type_id
,
2035 int (*visit_fun
) (const char *hval
,
2037 ctf_dict_t
**inputs
,
2040 int already_visited
,
2046 void *arg
, unsigned long depth
)
2048 ctf_dedup_t
*d
= &output
->ctf_dedup
;
2053 const char *whaterr
;
2055 input_num
= CTF_DEDUP_GID_TO_INPUT (type_id
);
2056 fp
= inputs
[input_num
];
2057 type
= CTF_DEDUP_GID_TO_TYPE (type_id
);
2059 ctf_dprintf ("%lu: Starting walk over type %s, %i/%lx (%p), from %s, "
2060 "kind %i\n", depth
, hval
, input_num
, type
, (void *) fp
,
2061 ctf_link_input_name (fp
), ctf_type_kind_unsliced (fp
, type
));
2063 /* Get the single call we do if this type has already been visited out of the
2066 return visit_fun (hval
, output
, inputs
, ninputs
, parents
, visited
, fp
,
2067 type
, type_id
, depth
, arg
);
2069 /* This macro is really ugly, but the alternative is repeating this code many
2070 times, which is worse. */
2072 #define CTF_TYPE_WALK(type, errlabel, errmsg) \
2076 const char *hashval; \
2077 int cited_type_input_num = input_num; \
2079 if ((fp->ctf_flags & LCTF_CHILD) && (LCTF_TYPE_ISPARENT (fp, type))) \
2080 cited_type_input_num = parents[input_num]; \
2082 type_id = CTF_DEDUP_GID (output, cited_type_input_num, type); \
2086 ctf_dprintf ("Walking: unimplemented type\n"); \
2090 ctf_dprintf ("Looking up ID %i/%lx in type hashes\n", \
2091 cited_type_input_num, type); \
2092 hashval = ctf_dynhash_lookup (d->cd_type_hashes, type_id); \
2093 if (!ctf_assert (output, hashval)) \
2095 whaterr = N_("error looking up ID in type hashes"); \
2098 ctf_dprintf ("ID %i/%lx has hash %s\n", cited_type_input_num, type, \
2101 ret = ctf_dedup_rwalk_output_mapping (output, inputs, ninputs, parents, \
2102 already_visited, hashval, \
2103 visit_fun, arg, depth); \
2112 switch (ctf_type_kind_unsliced (fp
, type
))
2119 /* No types referenced. */
2123 case CTF_K_VOLATILE
:
2125 case CTF_K_RESTRICT
:
2128 CTF_TYPE_WALK (ctf_type_reference (fp
, type
), err
,
2129 N_("error during referenced type walk"));
2136 if (ctf_array_info (fp
, type
, &ar
) < 0)
2138 whaterr
= N_("error during array info lookup");
2142 CTF_TYPE_WALK (ar
.ctr_contents
, err
,
2143 N_("error during array contents type walk"));
2144 CTF_TYPE_WALK (ar
.ctr_index
, err
,
2145 N_("error during array index type walk"));
2149 case CTF_K_FUNCTION
:
2155 if (ctf_func_type_info (fp
, type
, &fi
) < 0)
2157 whaterr
= N_("error during func type info lookup");
2161 CTF_TYPE_WALK (fi
.ctc_return
, err
,
2162 N_("error during func return type walk"));
2164 if ((args
= calloc (fi
.ctc_argc
, sizeof (ctf_id_t
))) == NULL
)
2166 whaterr
= N_("error doing memory allocation");
2170 if (ctf_func_type_args (fp
, type
, fi
.ctc_argc
, args
) < 0)
2172 whaterr
= N_("error doing func arg type lookup");
2177 for (j
= 0; j
< fi
.ctc_argc
; j
++)
2178 CTF_TYPE_WALK (args
[j
], err_free_args
,
2179 N_("error during Func arg type walk"));
2189 /* We do not recursively traverse the members of structures: they are
2190 emitted later, in a separate pass. */
2193 whaterr
= N_("CTF dict corruption: unknown type kind");
2197 return visit_fun (hval
, output
, inputs
, ninputs
, parents
, visited
, fp
, type
,
2198 type_id
, depth
, arg
);
2201 ctf_set_errno (output
, ctf_errno (fp
));
2202 ctf_err_warn (output
, 0, 0, _("%s in input file %s at type ID %lx"),
2203 gettext (whaterr
), ctf_link_input_name (fp
), type
);
2207 /* Recursively traverse the output mapping, and do something with each type
2208 visited, from leaves to root. VISIT_FUN, called as recursion unwinds,
2209 returns a negative error code or zero. Type hashes may be visited more than
2210 once, but are not recursed through repeatedly: ALREADY_VISITED tracks whether
2211 types have already been visited. */
2213 ctf_dedup_rwalk_output_mapping (ctf_dict_t
*output
, ctf_dict_t
**inputs
,
2214 uint32_t ninputs
, uint32_t *parents
,
2215 ctf_dynset_t
*already_visited
,
2217 int (*visit_fun
) (const char *hval
,
2219 ctf_dict_t
**inputs
,
2222 int already_visited
,
2228 void *arg
, unsigned long depth
)
2230 ctf_dedup_t
*d
= &output
->ctf_dedup
;
2231 ctf_next_t
*i
= NULL
;
2234 ctf_dynset_t
*type_ids
;
2239 type_ids
= ctf_dynhash_lookup (d
->cd_output_mapping
, hval
);
2242 ctf_err_warn (output
, 0, ECTF_INTERNAL
,
2243 _("looked up type kind by nonexistent hash %s"), hval
);
2244 return ctf_set_errno (output
, ECTF_INTERNAL
);
2247 /* Have we seen this type before? */
2249 if (!ctf_dynset_exists (already_visited
, hval
, NULL
))
2251 /* Mark as already-visited immediately, to eliminate the possibility of
2252 cycles: but remember we have not actually visited it yet for the
2253 upcoming call to the visit_fun. (All our callers handle cycles
2254 properly themselves, so we can just abort them aggressively as soon as
2255 we find ourselves in one.) */
2258 if (ctf_dynset_cinsert (already_visited
, hval
) < 0)
2260 ctf_err_warn (output
, 0, ENOMEM
,
2261 _("out of memory tracking already-visited types"));
2262 return ctf_set_errno (output
, ENOMEM
);
2266 /* If this type is marked conflicted, traverse members and call
2267 ctf_dedup_rwalk_one_output_mapping on all the unique ones: otherwise, just
2268 pick a random one and use it. */
2270 if (!ctf_dynset_exists (d
->cd_conflicting_types
, hval
, NULL
))
2272 id
= ctf_dynset_lookup_any (type_ids
);
2273 if (!ctf_assert (output
, id
))
2276 return ctf_dedup_rwalk_one_output_mapping (output
, inputs
, ninputs
,
2277 parents
, already_visited
,
2278 visited
, id
, hval
, visit_fun
,
2282 while ((err
= ctf_dynset_next (type_ids
, &i
, &id
)) == 0)
2286 ret
= ctf_dedup_rwalk_one_output_mapping (output
, inputs
, ninputs
,
2287 parents
, already_visited
,
2289 visit_fun
, arg
, depth
);
2292 ctf_next_destroy (i
);
2293 return ret
; /* errno is set for us. */
2296 if (err
!= ECTF_NEXT_END
)
2298 ctf_err_warn (output
, 0, err
, _("cannot walk conflicted type"));
2299 return ctf_set_errno (output
, err
);
2305 typedef struct ctf_sort_om_cb_arg
2307 ctf_dict_t
**inputs
;
2310 } ctf_sort_om_cb_arg_t
;
2312 /* Sort the output mapping into order: types first appearing in earlier inputs
2313 first, parents preceding children: if types first appear in the same input,
2314 sort those with earlier ctf_id_t's first. */
2316 sort_output_mapping (const ctf_next_hkv_t
*one
, const ctf_next_hkv_t
*two
,
2319 ctf_sort_om_cb_arg_t
*arg
= (ctf_sort_om_cb_arg_t
*) arg_
;
2320 ctf_dedup_t
*d
= arg
->d
;
2321 const char *one_hval
= (const char *) one
->hkv_key
;
2322 const char *two_hval
= (const char *) two
->hkv_key
;
2323 void *one_gid
, *two_gid
;
2324 uint32_t one_ninput
;
2325 uint32_t two_ninput
;
2331 /* Inputs are always equal to themselves. */
2335 one_gid
= ctf_dynhash_lookup (d
->cd_output_first_gid
, one_hval
);
2336 two_gid
= ctf_dynhash_lookup (d
->cd_output_first_gid
, two_hval
);
2338 one_ninput
= CTF_DEDUP_GID_TO_INPUT (one_gid
);
2339 two_ninput
= CTF_DEDUP_GID_TO_INPUT (two_gid
);
2341 one_type
= CTF_DEDUP_GID_TO_TYPE (one_gid
);
2342 two_type
= CTF_DEDUP_GID_TO_TYPE (two_gid
);
2344 /* It's kind of hard to smuggle an assertion failure out of here. */
2345 assert (one_ninput
< arg
->ninputs
&& two_ninput
< arg
->ninputs
);
2347 one_fp
= arg
->inputs
[one_ninput
];
2348 two_fp
= arg
->inputs
[two_ninput
];
2350 /* Parents before children. */
2352 if (!(one_fp
->ctf_flags
& LCTF_CHILD
)
2353 && (two_fp
->ctf_flags
& LCTF_CHILD
))
2355 else if ((one_fp
->ctf_flags
& LCTF_CHILD
)
2356 && !(two_fp
->ctf_flags
& LCTF_CHILD
))
2359 /* ninput order, types appearing in earlier TUs first. */
2361 if (one_ninput
< two_ninput
)
2363 else if (two_ninput
< one_ninput
)
2366 /* Same TU. Earliest ctf_id_t first. They cannot be the same. */
2368 assert (one_type
!= two_type
);
2369 if (one_type
< two_type
)
2375 /* The public entry point to ctf_dedup_rwalk_output_mapping, above. */
2377 ctf_dedup_walk_output_mapping (ctf_dict_t
*output
, ctf_dict_t
**inputs
,
2378 uint32_t ninputs
, uint32_t *parents
,
2379 int (*visit_fun
) (const char *hval
,
2381 ctf_dict_t
**inputs
,
2384 int already_visited
,
2392 ctf_dynset_t
*already_visited
;
2393 ctf_next_t
*i
= NULL
;
2394 ctf_sort_om_cb_arg_t sort_arg
;
2398 if ((already_visited
= ctf_dynset_create (htab_hash_string
,
2401 return ctf_set_errno (output
, ENOMEM
);
2403 sort_arg
.inputs
= inputs
;
2404 sort_arg
.ninputs
= ninputs
;
2405 sort_arg
.d
= &output
->ctf_dedup
;
2407 while ((err
= ctf_dynhash_next_sorted (output
->ctf_dedup
.cd_output_mapping
,
2408 &i
, &k
, NULL
, sort_output_mapping
,
2411 const char *hval
= (const char *) k
;
2413 err
= ctf_dedup_rwalk_output_mapping (output
, inputs
, ninputs
, parents
,
2414 already_visited
, hval
, visit_fun
,
2418 ctf_next_destroy (i
);
2419 goto err
; /* errno is set for us. */
2422 if (err
!= ECTF_NEXT_END
)
2424 ctf_set_errno (output
, err
);
2425 ctf_err_warn (output
, 0, 0, _("cannot recurse over output mapping"));
2428 ctf_dynset_destroy (already_visited
);
2432 ctf_dynset_destroy (already_visited
);
2436 /* Possibly synthesise a synthetic forward in TARGET to subsitute for a
2437 conflicted per-TU type ID in INPUT with hash HVAL. Return its CTF ID, or 0
2438 if none was needed. */
2440 ctf_dedup_maybe_synthesize_forward (ctf_dict_t
*output
, ctf_dict_t
*target
,
2441 ctf_dict_t
*input
, ctf_id_t id
,
2444 ctf_dedup_t
*od
= &output
->ctf_dedup
;
2445 ctf_dedup_t
*td
= &target
->ctf_dedup
;
2448 const char *name
= ctf_type_name_raw (input
, id
);
2449 const char *decorated
;
2451 ctf_id_t emitted_forward
;
2453 if (!ctf_dynset_exists (od
->cd_conflicting_types
, hval
, NULL
)
2454 || target
->ctf_flags
& LCTF_CHILD
2456 || (((kind
= ctf_type_kind_unsliced (input
, id
)) != CTF_K_STRUCT
2457 && kind
!= CTF_K_UNION
&& kind
!= CTF_K_FORWARD
)))
2460 fwdkind
= ctf_type_kind_forwarded (input
, id
);
2462 ctf_dprintf ("Using synthetic forward for conflicted struct/union with "
2465 if (!ctf_assert (output
, name
))
2468 if ((decorated
= ctf_decorate_type_name (output
, name
, fwdkind
)) == NULL
)
2471 if (!ctf_dynhash_lookup_kv (td
->cd_output_emission_conflicted_forwards
,
2472 decorated
, NULL
, &v
))
2474 if ((emitted_forward
= ctf_add_forward (target
, CTF_ADD_ROOT
, name
,
2475 fwdkind
)) == CTF_ERR
)
2476 return ctf_set_typed_errno (output
, ctf_errno (target
));
2478 if (ctf_dynhash_cinsert (td
->cd_output_emission_conflicted_forwards
,
2479 decorated
, (void *) (uintptr_t)
2480 emitted_forward
) < 0)
2481 return ctf_set_typed_errno (output
, ENOMEM
);
2484 emitted_forward
= (ctf_id_t
) (uintptr_t) v
;
2486 ctf_dprintf ("Cross-TU conflicted struct: passing back forward, %lx\n",
2489 return emitted_forward
;
2492 /* Map a GID in some INPUT dict, in the form of an input number and a ctf_id_t,
2493 into a GID in a target output dict. If it returns 0, this is the
2494 unimplemented type, and the input type must have been 0. The OUTPUT dict is
2495 assumed to be the parent of the TARGET, if it is not the TARGET itself.
2497 Returns CTF_ERR on failure. Responds to an incoming CTF_ERR as an 'id' by
2498 returning CTF_ERR, to simplify callers. Errors are always propagated to the
2499 input, even if they relate to the target, for the same reason. (Target
2500 errors are expected to be very rare.)
2502 If the type in question is a citation of a conflicted type in a different TU,
2503 emit a forward of the right type in its place (if not already emitted), and
2504 record that forward in cd_output_emission_conflicted_forwards. This avoids
2505 the need to replicate the entire type graph below this point in the current
2506 TU (an appalling waste of space).
2508 TODO: maybe replace forwards in the same TU with their referents? Might
2509 make usability a bit better. */
2512 ctf_dedup_id_to_target (ctf_dict_t
*output
, ctf_dict_t
*target
,
2513 ctf_dict_t
**inputs
, uint32_t ninputs
,
2514 uint32_t *parents
, ctf_dict_t
*input
, int input_num
,
2517 ctf_dedup_t
*od
= &output
->ctf_dedup
;
2518 ctf_dedup_t
*td
= &target
->ctf_dedup
;
2519 ctf_dict_t
*err_fp
= input
;
2522 ctf_id_t emitted_forward
;
2524 /* The target type of an error is an error. */
2528 /* The unimplemented type's ID never changes. */
2531 ctf_dprintf ("%i/%lx: unimplemented type\n", input_num
, id
);
2535 ctf_dprintf ("Mapping %i/%lx to target %p (%s)\n", input_num
,
2536 id
, (void *) target
, ctf_link_input_name (target
));
2538 /* If the input type is in the parent type space, and this is a child, reset
2539 the input to the parent (which must already have been emitted, since
2540 emission of parent dicts happens before children). */
2541 if ((input
->ctf_flags
& LCTF_CHILD
) && (LCTF_TYPE_ISPARENT (input
, id
)))
2543 if (!ctf_assert (output
, parents
[input_num
] <= ninputs
))
2545 input
= inputs
[parents
[input_num
]];
2546 input_num
= parents
[input_num
];
2549 hval
= ctf_dynhash_lookup (od
->cd_type_hashes
,
2550 CTF_DEDUP_GID (output
, input_num
, id
));
2552 if (!ctf_assert (output
, hval
&& td
->cd_output_emission_hashes
))
2555 /* If this type is a conflicted tagged structure, union, or forward,
2556 substitute a synthetic forward instead, emitting it if need be. Only do
2557 this if the target is in the parent dict: if it's in the child dict, we can
2558 just point straight at the thing itself. Of course, we might be looking in
2559 the child dict right now and not find it and have to look in the parent, so
2560 we have to do this check twice. */
2562 emitted_forward
= ctf_dedup_maybe_synthesize_forward (output
, target
,
2564 switch (emitted_forward
)
2566 case 0: /* No forward needed. */
2569 ctf_set_errno (err_fp
, ctf_errno (output
));
2570 ctf_err_warn (err_fp
, 0, 0, _("cannot add synthetic forward for type "
2571 "%i/%lx"), input_num
, id
);
2574 return emitted_forward
;
2577 ctf_dprintf ("Looking up %i/%lx, hash %s, in target\n", input_num
, id
, hval
);
2579 target_id
= ctf_dynhash_lookup (td
->cd_output_emission_hashes
, hval
);
2582 /* Must be in the parent, so this must be a child, and they must not be
2584 ctf_dprintf ("Checking shared parent for target\n");
2585 if (!ctf_assert (output
, (target
!= output
)
2586 && (target
->ctf_flags
& LCTF_CHILD
)))
2589 target_id
= ctf_dynhash_lookup (od
->cd_output_emission_hashes
, hval
);
2591 emitted_forward
= ctf_dedup_maybe_synthesize_forward (output
, output
,
2593 switch (emitted_forward
)
2595 case 0: /* No forward needed. */
2598 ctf_err_warn (err_fp
, 0, ctf_errno (output
),
2599 _("cannot add synthetic forward for type %i/%lx"),
2601 return ctf_set_typed_errno (err_fp
, ctf_errno (output
));
2603 return emitted_forward
;
2606 if (!ctf_assert (output
, target_id
))
2608 return (ctf_id_t
) (uintptr_t) target_id
;
2611 /* Emit a single deduplicated TYPE with the given HVAL, located in a given
2612 INPUT, with the given (G)ID, into the shared OUTPUT or a
2613 possibly-newly-created per-CU dict. All the types this type depends upon
2614 have already been emitted. (This type itself may also have been emitted.)
2616 If the ARG is 1, this is a CU-mapped deduplication round mapping many
2617 ctf_dict_t's into precisely one: conflicting types should be marked
2618 non-root-visible. If the ARG is 0, conflicting types go into per-CU
2619 dictionaries stored in the input's ctf_dedup.cd_output: otherwise, everything
2620 is emitted directly into the output. No struct/union members are emitted.
2622 Optimization opportunity: trace the ancestry of non-root-visible types and
2623 elide all that neither have a root-visible type somewhere towards their root,
2624 nor have the type visible via any other route (the function info section,
2625 data object section, backtrace section etc). */
2628 ctf_dedup_emit_type (const char *hval
, ctf_dict_t
*output
, ctf_dict_t
**inputs
,
2629 uint32_t ninputs
, uint32_t *parents
, int already_visited
,
2630 ctf_dict_t
*input
, ctf_id_t type
, void *id
, int depth
,
2633 ctf_dedup_t
*d
= &output
->ctf_dedup
;
2634 int kind
= ctf_type_kind_unsliced (input
, type
);
2636 ctf_dict_t
*target
= output
;
2637 ctf_dict_t
*real_input
;
2638 const ctf_type_t
*tp
;
2639 int input_num
= CTF_DEDUP_GID_TO_INPUT (id
);
2640 int output_num
= (uint32_t) -1; /* 'shared' */
2641 int cu_mapped
= *(int *)arg
;
2645 ctf_next_t
*i
= NULL
;
2648 ctf_id_t maybe_dup
= 0;
2650 const char *errtype
;
2651 int emission_hashed
= 0;
2653 /* We don't want to re-emit something we've already emitted. */
2655 if (already_visited
)
2658 ctf_dprintf ("%i: Emitting type with hash %s from %s: determining target\n",
2659 depth
, hval
, ctf_link_input_name (input
));
2661 /* Conflicting types go into a per-CU output dictionary, unless this is a
2662 CU-mapped run. The import is not refcounted, since it goes into the
2663 ctf_link_outputs dict of the output that is its parent. */
2664 is_conflicting
= ctf_dynset_exists (d
->cd_conflicting_types
, hval
, NULL
);
2666 if (is_conflicting
&& !cu_mapped
)
2668 ctf_dprintf ("%i: Type %s in %i/%lx is conflicted: "
2669 "inserting into per-CU target.\n",
2670 depth
, hval
, input_num
, type
);
2672 if (input
->ctf_dedup
.cd_output
)
2673 target
= input
->ctf_dedup
.cd_output
;
2678 if ((target
= ctf_create (&err
)) == NULL
)
2680 ctf_err_warn (output
, 0, err
,
2681 _("cannot create per-CU CTF archive for CU %s"),
2682 ctf_link_input_name (input
));
2683 return ctf_set_errno (output
, err
);
2686 target
->ctf_flags
|= LCTF_STRICT_NO_DUP_ENUMERATORS
;
2687 ctf_import_unref (target
, output
);
2688 if (ctf_cuname (input
) != NULL
)
2689 ctf_cuname_set (target
, ctf_cuname (input
));
2691 ctf_cuname_set (target
, "unnamed-CU");
2692 ctf_parent_name_set (target
, _CTF_SECTION
);
2694 input
->ctf_dedup
.cd_output
= target
;
2695 input
->ctf_link_in_out
= target
;
2696 target
->ctf_link_in_out
= input
;
2698 output_num
= input_num
;
2702 if ((tp
= ctf_lookup_by_id (&real_input
, type
)) == NULL
)
2704 ctf_err_warn (output
, 0, ctf_errno (input
),
2705 _("%s: lookup failure for type %lx"),
2706 ctf_link_input_name (real_input
), type
);
2707 return ctf_set_errno (output
, ctf_errno (input
));
2710 name
= ctf_strraw (real_input
, tp
->ctt_name
);
2711 isroot
= LCTF_INFO_ISROOT (real_input
, tp
->ctt_info
);
2713 /* Hide conflicting types, if we were asked to: also hide if a type with this
2714 name already exists and is not a forward, or if this type is hidden on the
2716 if (cu_mapped
&& is_conflicting
)
2719 && (maybe_dup
= ctf_lookup_by_rawname (target
, kind
, name
)) != 0)
2721 if (ctf_type_kind (target
, maybe_dup
) != CTF_K_FORWARD
)
2725 ctf_dprintf ("%i: Emitting type with hash %s (%s), into target %i/%p\n",
2726 depth
, hval
, name
? name
: "", input_num
, (void *) target
);
2728 if (!target
->ctf_dedup
.cd_output_emission_hashes
)
2729 if ((target
->ctf_dedup
.cd_output_emission_hashes
2730 = ctf_dynhash_create (ctf_hash_string
, ctf_hash_eq_string
,
2731 NULL
, NULL
)) == NULL
)
2734 if (!target
->ctf_dedup
.cd_output_emission_conflicted_forwards
)
2735 if ((target
->ctf_dedup
.cd_output_emission_conflicted_forwards
2736 = ctf_dynhash_create (ctf_hash_string
, ctf_hash_eq_string
,
2737 NULL
, NULL
)) == NULL
)
2743 /* These are types that CTF cannot encode, marked as such by the
2745 errtype
= _("unknown type");
2746 if ((new_type
= ctf_add_unknown (target
, isroot
, name
)) == CTF_ERR
)
2750 /* This will do nothing if the type to which this forwards already exists,
2751 and will be replaced with such a type if it appears later. */
2753 errtype
= _("forward");
2754 if ((new_type
= ctf_add_forward (target
, isroot
, name
,
2755 ctf_type_kind_forwarded (input
, type
)))
2762 errtype
= _("float/int");
2763 if (ctf_type_encoding (input
, type
, &ep
) < 0)
2764 goto err_input
; /* errno is set for us. */
2765 if ((new_type
= ctf_add_encoded (target
, isroot
, name
, &ep
, kind
))
2773 errtype
= _("enum");
2774 if ((new_type
= ctf_add_enum (target
, isroot
, name
)) == CTF_ERR
)
2775 goto err_input
; /* errno is set for us. */
2777 while ((name
= ctf_enum_next (input
, type
, &i
, &val
)) != NULL
)
2779 if (ctf_add_enumerator (target
, new_type
, name
, val
) < 0)
2781 ctf_err_warn (target
, 0, ctf_errno (target
),
2782 _("%s (%i): cannot add enumeration value %s "
2783 "from input type %lx"),
2784 ctf_link_input_name (input
), input_num
, name
,
2786 ctf_next_destroy (i
);
2787 return ctf_set_errno (output
, ctf_errno (target
));
2790 if (ctf_errno (input
) != ECTF_NEXT_END
)
2796 errtype
= _("typedef");
2798 ref
= ctf_type_reference (input
, type
);
2799 if ((ref
= ctf_dedup_id_to_target (output
, target
, inputs
, ninputs
,
2800 parents
, input
, input_num
,
2802 goto err_input
; /* errno is set for us. */
2804 if ((new_type
= ctf_add_typedef (target
, isroot
, name
, ref
)) == CTF_ERR
)
2805 goto err_target
; /* errno is set for us. */
2808 case CTF_K_VOLATILE
:
2810 case CTF_K_RESTRICT
:
2812 errtype
= _("pointer or cvr-qual");
2814 ref
= ctf_type_reference (input
, type
);
2815 if ((ref
= ctf_dedup_id_to_target (output
, target
, inputs
, ninputs
,
2816 parents
, input
, input_num
,
2818 goto err_input
; /* errno is set for us. */
2820 if ((new_type
= ctf_add_reftype (target
, isroot
, ref
, kind
)) == CTF_ERR
)
2821 goto err_target
; /* errno is set for us. */
2825 errtype
= _("slice");
2827 if (ctf_type_encoding (input
, type
, &ep
) < 0)
2828 goto err_input
; /* errno is set for us. */
2830 ref
= ctf_type_reference (input
, type
);
2831 if ((ref
= ctf_dedup_id_to_target (output
, target
, inputs
, ninputs
,
2832 parents
, input
, input_num
,
2836 if ((new_type
= ctf_add_slice (target
, isroot
, ref
, &ep
)) == CTF_ERR
)
2844 errtype
= _("array info");
2845 if (ctf_array_info (input
, type
, &ar
) < 0)
2848 ar
.ctr_contents
= ctf_dedup_id_to_target (output
, target
, inputs
,
2849 ninputs
, parents
, input
,
2850 input_num
, ar
.ctr_contents
);
2851 ar
.ctr_index
= ctf_dedup_id_to_target (output
, target
, inputs
, ninputs
,
2852 parents
, input
, input_num
,
2855 if (ar
.ctr_contents
== CTF_ERR
|| ar
.ctr_index
== CTF_ERR
)
2858 if ((new_type
= ctf_add_array (target
, isroot
, &ar
)) == CTF_ERR
)
2864 case CTF_K_FUNCTION
:
2870 errtype
= _("function");
2871 if (ctf_func_type_info (input
, type
, &fi
) < 0)
2874 fi
.ctc_return
= ctf_dedup_id_to_target (output
, target
, inputs
, ninputs
,
2875 parents
, input
, input_num
,
2877 if (fi
.ctc_return
== CTF_ERR
)
2880 if ((args
= calloc (fi
.ctc_argc
, sizeof (ctf_id_t
))) == NULL
)
2882 ctf_set_errno (input
, ENOMEM
);
2886 errtype
= _("function args");
2887 if (ctf_func_type_args (input
, type
, fi
.ctc_argc
, args
) < 0)
2893 for (j
= 0; j
< fi
.ctc_argc
; j
++)
2895 args
[j
] = ctf_dedup_id_to_target (output
, target
, inputs
, ninputs
,
2896 parents
, input
, input_num
,
2898 if (args
[j
] == CTF_ERR
)
2902 if ((new_type
= ctf_add_function (target
, isroot
,
2903 &fi
, args
)) == CTF_ERR
)
2915 size_t size
= ctf_type_size (input
, type
);
2917 /* Insert the structure itself, so other types can refer to it. */
2919 errtype
= _("structure/union");
2920 if (kind
== CTF_K_STRUCT
)
2921 new_type
= ctf_add_struct_sized (target
, isroot
, name
, size
);
2923 new_type
= ctf_add_union_sized (target
, isroot
, name
, size
);
2925 if (new_type
== CTF_ERR
)
2928 out_id
= CTF_DEDUP_GID (output
, output_num
, new_type
);
2929 ctf_dprintf ("%i: Noting need to emit members of %p -> %p\n", depth
,
2931 /* Record the need to emit the members of this structure later. */
2932 if (ctf_dynhash_insert (d
->cd_emission_struct_members
, id
, out_id
) < 0)
2934 ctf_set_errno (target
, errno
);
2940 ctf_err_warn (output
, 0, ECTF_CORRUPT
, _("%s: unknown type kind for "
2942 ctf_link_input_name (input
), type
);
2943 return ctf_set_errno (output
, ECTF_CORRUPT
);
2946 if (!emission_hashed
2948 && ctf_dynhash_cinsert (target
->ctf_dedup
.cd_output_emission_hashes
,
2949 hval
, (void *) (uintptr_t) new_type
) < 0)
2951 ctf_err_warn (output
, 0, ENOMEM
, _("out of memory tracking deduplicated "
2952 "global type IDs"));
2953 return ctf_set_errno (output
, ENOMEM
);
2956 if (!emission_hashed
&& new_type
!= 0)
2957 ctf_dprintf ("%i: Inserted %s, %i/%lx -> %lx into emission hash for "
2958 "target %p (%s)\n", depth
, hval
, input_num
, type
, new_type
,
2959 (void *) target
, ctf_link_input_name (target
));
2964 ctf_err_warn (output
, 0, ENOMEM
, _("out of memory creating emission-tracking "
2966 return ctf_set_errno (output
, ENOMEM
);
2969 ctf_err_warn (output
, 0, ctf_errno (input
),
2970 _("%s (%i): while emitting deduplicated %s, error getting "
2971 "input type %lx"), ctf_link_input_name (input
),
2972 input_num
, errtype
, type
);
2973 return ctf_set_errno (output
, ctf_errno (input
));
2975 ctf_err_warn (output
, 0, ctf_errno (target
),
2976 _("%s (%i): while emitting deduplicated %s, error emitting "
2977 "target type from input type %lx"),
2978 ctf_link_input_name (input
), input_num
,
2980 return ctf_set_errno (output
, ctf_errno (target
));
2983 /* Traverse the cd_emission_struct_members and emit the members of all
2984 structures and unions. All other types are emitted and complete by this
2988 ctf_dedup_emit_struct_members (ctf_dict_t
*output
, ctf_dict_t
**inputs
,
2989 uint32_t ninputs
, uint32_t *parents
)
2991 ctf_dedup_t
*d
= &output
->ctf_dedup
;
2992 ctf_next_t
*i
= NULL
;
2993 void *input_id
, *target_id
;
2995 ctf_dict_t
*err_fp
, *input_fp
;
2999 while ((err
= ctf_dynhash_next (d
->cd_emission_struct_members
, &i
,
3000 &input_id
, &target_id
)) == 0)
3002 ctf_next_t
*j
= NULL
;
3004 uint32_t target_num
;
3005 ctf_id_t input_type
, target_type
;
3010 input_num
= CTF_DEDUP_GID_TO_INPUT (input_id
);
3011 input_fp
= inputs
[input_num
];
3012 input_type
= CTF_DEDUP_GID_TO_TYPE (input_id
);
3014 /* The output is either -1 (for the shared, parent output dict) or the
3015 number of the corresponding input. */
3016 target_num
= CTF_DEDUP_GID_TO_INPUT (target_id
);
3017 if (target_num
== (uint32_t) -1)
3021 target
= inputs
[target_num
]->ctf_dedup
.cd_output
;
3022 if (!ctf_assert (output
, target
))
3025 err_type
= input_type
;
3029 target_type
= CTF_DEDUP_GID_TO_TYPE (target_id
);
3031 while ((offset
= ctf_member_next (input_fp
, input_type
, &j
, &name
,
3032 &membtype
, 0)) >= 0)
3035 err_type
= target_type
;
3036 if ((membtype
= ctf_dedup_id_to_target (output
, target
, inputs
,
3037 ninputs
, parents
, input_fp
,
3039 membtype
)) == CTF_ERR
)
3041 ctf_next_destroy (j
);
3047 #ifdef ENABLE_LIBCTF_HASH_DEBUGGING
3048 ctf_dprintf ("Emitting %s, offset %zi\n", name
, offset
);
3050 if (ctf_add_member_offset (target
, target_type
, name
,
3051 membtype
, offset
) < 0)
3053 ctf_next_destroy (j
);
3057 if (ctf_errno (input_fp
) != ECTF_NEXT_END
)
3059 err
= ctf_errno (input_fp
);
3060 ctf_next_destroy (i
);
3064 if (err
!= ECTF_NEXT_END
)
3069 ctf_next_destroy (i
);
3070 ctf_err_warn (output
, 0, ctf_errno (err_fp
),
3071 _("%s (%i): error emitting members for structure type %lx"),
3072 ctf_link_input_name (input_fp
), input_num
, err_type
);
3073 return ctf_set_errno (output
, ctf_errno (err_fp
));
3075 ctf_err_warn (output
, 0, err
, _("iteration failure emitting "
3076 "structure members"));
3077 return ctf_set_errno (output
, err
);
3080 /* Emit deduplicated types into the outputs. The shared type repository is
3081 OUTPUT, on which the ctf_dedup function must have already been called. The
3082 PARENTS array contains the INPUTS index of the parent dict for every child
3083 dict at the corresponding index in the INPUTS (for non-child dicts, the value
3084 is undefined and can just be left at zero).
3086 Return an array of fps with content emitted into them (starting with OUTPUT,
3087 which is the parent of all others, then all the newly-generated outputs).
3089 If CU_MAPPED is set, this is a first pass for a link with a non-empty CU
3090 mapping: only one output will result. */
3093 ctf_dedup_emit (ctf_dict_t
*output
, ctf_dict_t
**inputs
, uint32_t ninputs
,
3094 uint32_t *parents
, uint32_t *noutputs
, int cu_mapped
)
3096 size_t num_outputs
= 1; /* Always at least one output: us. */
3097 ctf_dict_t
**outputs
;
3101 ctf_dprintf ("Triggering emission.\n");
3102 if (ctf_dedup_walk_output_mapping (output
, inputs
, ninputs
, parents
,
3103 ctf_dedup_emit_type
, &cu_mapped
) < 0)
3104 return NULL
; /* errno is set for us. */
3106 ctf_dprintf ("Populating struct members.\n");
3107 if (ctf_dedup_emit_struct_members (output
, inputs
, ninputs
, parents
) < 0)
3108 return NULL
; /* errno is set for us. */
3110 for (i
= 0; i
< ninputs
; i
++)
3112 if (inputs
[i
]->ctf_dedup
.cd_output
)
3116 if (!ctf_assert (output
, !cu_mapped
|| (cu_mapped
&& num_outputs
== 1)))
3119 if ((outputs
= calloc (num_outputs
, sizeof (ctf_dict_t
*))) == NULL
)
3121 ctf_set_errno (output
, ENOMEM
);
3122 ctf_err_warn (output
, 0, 0,
3123 _("out of memory allocating link outputs array"));
3126 *noutputs
= num_outputs
;
3130 output
->ctf_refcnt
++;
3133 for (i
= 0; i
< ninputs
; i
++)
3135 if (inputs
[i
]->ctf_dedup
.cd_output
)
3137 *walk
= inputs
[i
]->ctf_dedup
.cd_output
;
3138 inputs
[i
]->ctf_dedup
.cd_output
= NULL
;
3146 /* Determine what type SRC_FP / SRC_TYPE was emitted as in the FP, which
3147 must be the shared dict or have it as a parent: return 0 if none. The SRC_FP
3148 must be a past input to ctf_dedup. */
3151 ctf_dedup_type_mapping (ctf_dict_t
*fp
, ctf_dict_t
*src_fp
, ctf_id_t src_type
)
3153 ctf_dict_t
*output
= NULL
;
3161 /* It is an error (an internal error in the caller, in ctf-link.c) to call
3162 this with an FP that is not a per-CU output or shared output dict, or with
3163 a SRC_FP that was not passed to ctf_dedup as an input; it is an internal
3164 error in ctf-dedup for the type passed not to have been hashed, though if
3165 the src_fp is a child dict and the type is not a child type, it will have
3166 been hashed under the GID corresponding to the parent. */
3168 if (fp
->ctf_dedup
.cd_type_hashes
!= NULL
)
3170 else if (fp
->ctf_parent
&& fp
->ctf_parent
->ctf_dedup
.cd_type_hashes
!= NULL
)
3171 output
= fp
->ctf_parent
;
3174 ctf_set_errno (fp
, ECTF_INTERNAL
);
3175 ctf_err_warn (fp
, 0, 0,
3176 _("dict %p passed to ctf_dedup_type_mapping is not a "
3177 "deduplicated output"), (void *) fp
);
3181 if (src_fp
->ctf_parent
&& ctf_type_isparent (src_fp
, src_type
))
3182 src_fp
= src_fp
->ctf_parent
;
3184 d
= &output
->ctf_dedup
;
3186 found
= ctf_dynhash_lookup_kv (d
->cd_input_nums
, src_fp
, NULL
, &num_ptr
);
3187 if (!ctf_assert (output
, found
!= 0))
3188 return CTF_ERR
; /* errno is set for us. */
3189 input_num
= (uintptr_t) num_ptr
;
3191 hval
= ctf_dynhash_lookup (d
->cd_type_hashes
,
3192 CTF_DEDUP_GID (output
, input_num
, src_type
));
3194 if (!ctf_assert (output
, hval
!= NULL
))
3195 return CTF_ERR
; /* errno is set for us. */
3197 /* The emission hashes may be unset if this dict was created after
3198 deduplication to house variables or other things that would conflict if
3199 stored in the shared dict. */
3200 if (fp
->ctf_dedup
.cd_output_emission_hashes
)
3201 if (ctf_dynhash_lookup_kv (fp
->ctf_dedup
.cd_output_emission_hashes
, hval
,
3203 return (ctf_id_t
) (uintptr_t) type_ptr
;
3207 ctf_dict_t
*pfp
= fp
->ctf_parent
;
3208 if (pfp
->ctf_dedup
.cd_output_emission_hashes
)
3209 if (ctf_dynhash_lookup_kv (pfp
->ctf_dedup
.cd_output_emission_hashes
,
3210 hval
, NULL
, &type_ptr
))
3211 return (ctf_id_t
) (uintptr_t) type_ptr
;