1*38fd1498Szrj /* Copyright (C) 2013-2018 Free Software Foundation, Inc.
2*38fd1498Szrj
3*38fd1498Szrj This file is part of GCC.
4*38fd1498Szrj
5*38fd1498Szrj GCC is free software; you can redistribute it and/or modify it under
6*38fd1498Szrj the terms of the GNU General Public License as published by the Free
7*38fd1498Szrj Software Foundation; either version 3, or (at your option) any later
8*38fd1498Szrj version.
9*38fd1498Szrj
10*38fd1498Szrj GCC is distributed in the hope that it will be useful, but WITHOUT ANY
11*38fd1498Szrj WARRANTY; without even the implied warranty of MERCHANTABILITY or
12*38fd1498Szrj FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
13*38fd1498Szrj for more details.
14*38fd1498Szrj
15*38fd1498Szrj You should have received a copy of the GNU General Public License
16*38fd1498Szrj along with GCC; see the file COPYING3. If not see
17*38fd1498Szrj <http://www.gnu.org/licenses/>. */
18*38fd1498Szrj
19*38fd1498Szrj /* Virtual Table Pointer Security Pass - Detect corruption of vtable pointers
20*38fd1498Szrj before using them for virtual method dispatches. */
21*38fd1498Szrj
22*38fd1498Szrj /* This file is part of the vtable security feature implementation.
23*38fd1498Szrj The vtable security feature is designed to detect when a virtual
24*38fd1498Szrj call is about to be made through an invalid vtable pointer
25*38fd1498Szrj (possibly due to data corruption or malicious attacks). The
26*38fd1498Szrj compiler finds every virtual call, and inserts a verification call
27*38fd1498Szrj before the virtual call. The verification call takes the actual
28*38fd1498Szrj vtable pointer value in the object through which the virtual call
29*38fd1498Szrj is being made, and compares the vtable pointer against a set of all
30*38fd1498Szrj valid vtable pointers that the object could contain (this set is
31*38fd1498Szrj based on the declared type of the object). If the pointer is in
32*38fd1498Szrj the valid set, execution is allowed to continue; otherwise the
33*38fd1498Szrj program is halted.
34*38fd1498Szrj
35*38fd1498Szrj There are several pieces needed in order to make this work: 1. For
36*38fd1498Szrj every virtual class in the program (i.e. a class that contains
37*38fd1498Szrj virtual methods), we need to build the set of all possible valid
38*38fd1498Szrj vtables that an object of that class could point to. This includes
39*38fd1498Szrj vtables for any class(es) that inherit from the class under
40*38fd1498Szrj consideration. 2. For every such data set we build up, we need a
41*38fd1498Szrj way to find and reference the data set. This is complicated by the
42*38fd1498Szrj fact that the real vtable addresses are not known until runtime,
43*38fd1498Szrj when the program is loaded into memory, but we need to reference the
44*38fd1498Szrj sets at compile time when we are inserting verification calls into
45*38fd1498Szrj the program. 3. We need to find every virtual call in the program,
46*38fd1498Szrj and insert the verification call (with the appropriate arguments)
47*38fd1498Szrj before the virtual call. 4. We need some runtime library pieces:
48*38fd1498Szrj the code to build up the data sets at runtime; the code to actually
49*38fd1498Szrj perform the verification using the data sets; and some code to set
50*38fd1498Szrj protections on the data sets, so they themselves do not become
51*38fd1498Szrj hacker targets.
52*38fd1498Szrj
53*38fd1498Szrj To find and reference the set of valid vtable pointers for any given
54*38fd1498Szrj virtual class, we create a special global variable for each virtual
55*38fd1498Szrj class. We refer to this as the "vtable map variable" for that
56*38fd1498Szrj class. The vtable map variable has the type "void *", and is
57*38fd1498Szrj initialized by the compiler to NULL. At runtime when the set of
58*38fd1498Szrj valid vtable pointers for a virtual class, e.g. class Foo, is built,
59*38fd1498Szrj the vtable map variable for class Foo is made to point to the set.
60*38fd1498Szrj During compile time, when the compiler is inserting verification
61*38fd1498Szrj calls into the program, it passes the vtable map variable for the
62*38fd1498Szrj appropriate class to the verification call, so that at runtime the
63*38fd1498Szrj verification call can find the appropriate data set.
64*38fd1498Szrj
65*38fd1498Szrj The actual set of valid vtable pointers for a virtual class,
66*38fd1498Szrj e.g. class Foo, cannot be built until runtime, when the vtables get
67*38fd1498Szrj loaded into memory and their addresses are known. But the knowledge
68*38fd1498Szrj about which vtables belong in which class' hierarchy is only known
69*38fd1498Szrj at compile time. Therefore at compile time we collect class
70*38fd1498Szrj hierarchy and vtable information about every virtual class, and we
71*38fd1498Szrj generate calls to build up the data sets at runtime. To build the
72*38fd1498Szrj data sets, we call one of the functions we add to the runtime
73*38fd1498Szrj library, __VLTRegisterPair. __VLTRegisterPair takes two arguments,
74*38fd1498Szrj a vtable map variable and the address of a vtable. If the vtable
75*38fd1498Szrj map variable is currently NULL, it creates a new data set (hash
76*38fd1498Szrj table), makes the vtable map variable point to the new data set, and
77*38fd1498Szrj inserts the vtable address into the data set. If the vtable map
78*38fd1498Szrj variable is not NULL, it just inserts the vtable address into the
79*38fd1498Szrj data set. In order to make sure that our data sets are built before
80*38fd1498Szrj any verification calls happen, we create a special constructor
81*38fd1498Szrj initialization function for each compilation unit, give it a very
82*38fd1498Szrj high initialization priority, and insert all of our calls to
83*38fd1498Szrj __VLTRegisterPair into our special constructor initialization
84*38fd1498Szrj function.
85*38fd1498Szrj
86*38fd1498Szrj The vtable verification feature is controlled by the flag
87*38fd1498Szrj '-fvtable-verify='. There are three flavors of this:
88*38fd1498Szrj '-fvtable-verify=std', '-fvtable-verify=preinit', and
89*38fd1498Szrj '-fvtable-verify=none'. If the option '-fvtable-verfy=preinit' is
90*38fd1498Szrj used, then our constructor initialization function gets put into the
91*38fd1498Szrj preinit array. This is necessary if there are data sets that need
92*38fd1498Szrj to be built very early in execution. If the constructor
93*38fd1498Szrj initialization function gets put into the preinit array, the we also
94*38fd1498Szrj add calls to __VLTChangePermission at the beginning and end of the
95*38fd1498Szrj function. The call at the beginning sets the permissions on the
96*38fd1498Szrj data sets and vtable map variables to read/write, and the one at the
97*38fd1498Szrj end makes them read-only. If the '-fvtable-verify=std' option is
98*38fd1498Szrj used, the constructor initialization functions are executed at their
99*38fd1498Szrj normal time, and the __VLTChangePermission calls are handled
100*38fd1498Szrj differently (see the comments in libstdc++-v3/libsupc++/vtv_rts.cc).
101*38fd1498Szrj The option '-fvtable-verify=none' turns off vtable verification.
102*38fd1498Szrj
103*38fd1498Szrj This file contains code for the tree pass that goes through all the
104*38fd1498Szrj statements in each basic block, looking for virtual calls, and
105*38fd1498Szrj inserting a call to __VLTVerifyVtablePointer (with appropriate
106*38fd1498Szrj arguments) before each one. It also contains the hash table
107*38fd1498Szrj functions for the data structures used for collecting the class
108*38fd1498Szrj hierarchy data and building/maintaining the vtable map variable data
109*38fd1498Szrj are defined in gcc/vtable-verify.h. These data structures are
110*38fd1498Szrj shared with the code in the C++ front end that collects the class
111*38fd1498Szrj hierarchy & vtable information and generates the vtable map
112*38fd1498Szrj variables (see cp/vtable-class-hierarchy.c). This tree pass should
113*38fd1498Szrj run just before the gimple is converted to RTL.
114*38fd1498Szrj
115*38fd1498Szrj Some implementation details for this pass:
116*38fd1498Szrj
117*38fd1498Szrj To find all of the virtual calls, we iterate through all the
118*38fd1498Szrj gimple statements in each basic block, looking for any call
119*38fd1498Szrj statement with the code "OBJ_TYPE_REF". Once we have found the
120*38fd1498Szrj virtual call, we need to find the vtable pointer through which the
121*38fd1498Szrj call is being made, and the type of the object containing the
122*38fd1498Szrj pointer (to find the appropriate vtable map variable). We then use
123*38fd1498Szrj these to build a call to __VLTVerifyVtablePointer, passing the
124*38fd1498Szrj vtable map variable, and the vtable pointer. We insert the
125*38fd1498Szrj verification call just after the gimple statement that gets the
126*38fd1498Szrj vtable pointer out of the object, and we update the next
127*38fd1498Szrj statement to depend on the result returned from
128*38fd1498Szrj __VLTVerifyVtablePointer (the vtable pointer value), to ensure
129*38fd1498Szrj subsequent compiler phases don't remove or reorder the call (it's no
130*38fd1498Szrj good to have the verification occur after the virtual call, for
131*38fd1498Szrj example). To find the vtable pointer being used (and the type of
132*38fd1498Szrj the object) we search backwards through the def_stmts chain from the
133*38fd1498Szrj virtual call (see verify_bb_vtables for more details). */
134*38fd1498Szrj
135*38fd1498Szrj #include "config.h"
136*38fd1498Szrj #include "system.h"
137*38fd1498Szrj #include "coretypes.h"
138*38fd1498Szrj #include "backend.h"
139*38fd1498Szrj #include "tree.h"
140*38fd1498Szrj #include "gimple.h"
141*38fd1498Szrj #include "tree-pass.h"
142*38fd1498Szrj #include "ssa.h"
143*38fd1498Szrj #include "gimple-iterator.h"
144*38fd1498Szrj
145*38fd1498Szrj #include "vtable-verify.h"
146*38fd1498Szrj
147*38fd1498Szrj unsigned num_vtable_map_nodes = 0;
148*38fd1498Szrj int total_num_virtual_calls = 0;
149*38fd1498Szrj int total_num_verified_vcalls = 0;
150*38fd1498Szrj
151*38fd1498Szrj extern GTY(()) tree verify_vtbl_ptr_fndecl;
152*38fd1498Szrj tree verify_vtbl_ptr_fndecl = NULL_TREE;
153*38fd1498Szrj
154*38fd1498Szrj /* Keep track of whether or not any virtual call were verified. */
155*38fd1498Szrj static bool any_verification_calls_generated = false;
156*38fd1498Szrj
157*38fd1498Szrj unsigned int vtable_verify_main (void);
158*38fd1498Szrj
159*38fd1498Szrj
160*38fd1498Szrj /* The following few functions are for the vtbl pointer hash table
161*38fd1498Szrj in the 'registered' field of the struct vtable_map_node. The hash
162*38fd1498Szrj table keeps track of which vtable pointers have been used in
163*38fd1498Szrj calls to __VLTRegisterPair with that particular vtable map variable. */
164*38fd1498Szrj
165*38fd1498Szrj /* This function checks to see if a particular VTABLE_DECL and OFFSET are
166*38fd1498Szrj already in the 'registered' hash table for NODE. */
167*38fd1498Szrj
168*38fd1498Szrj bool
vtbl_map_node_registration_find(struct vtbl_map_node * node,tree vtable_decl,unsigned offset)169*38fd1498Szrj vtbl_map_node_registration_find (struct vtbl_map_node *node,
170*38fd1498Szrj tree vtable_decl,
171*38fd1498Szrj unsigned offset)
172*38fd1498Szrj {
173*38fd1498Szrj struct vtable_registration key;
174*38fd1498Szrj struct vtable_registration **slot;
175*38fd1498Szrj
176*38fd1498Szrj gcc_assert (node && node->registered);
177*38fd1498Szrj
178*38fd1498Szrj key.vtable_decl = vtable_decl;
179*38fd1498Szrj slot = node->registered->find_slot (&key, NO_INSERT);
180*38fd1498Szrj
181*38fd1498Szrj if (slot && (*slot))
182*38fd1498Szrj {
183*38fd1498Szrj unsigned i;
184*38fd1498Szrj for (i = 0; i < ((*slot)->offsets).length (); ++i)
185*38fd1498Szrj if ((*slot)->offsets[i] == offset)
186*38fd1498Szrj return true;
187*38fd1498Szrj }
188*38fd1498Szrj
189*38fd1498Szrj return false;
190*38fd1498Szrj }
191*38fd1498Szrj
192*38fd1498Szrj /* This function inserts VTABLE_DECL and OFFSET into the 'registered'
193*38fd1498Szrj hash table for NODE. It returns a boolean indicating whether or not
194*38fd1498Szrj it actually inserted anything. */
195*38fd1498Szrj
196*38fd1498Szrj bool
vtbl_map_node_registration_insert(struct vtbl_map_node * node,tree vtable_decl,unsigned offset)197*38fd1498Szrj vtbl_map_node_registration_insert (struct vtbl_map_node *node,
198*38fd1498Szrj tree vtable_decl,
199*38fd1498Szrj unsigned offset)
200*38fd1498Szrj {
201*38fd1498Szrj struct vtable_registration key;
202*38fd1498Szrj struct vtable_registration **slot;
203*38fd1498Szrj bool inserted_something = false;
204*38fd1498Szrj
205*38fd1498Szrj if (!node || !node->registered)
206*38fd1498Szrj return false;
207*38fd1498Szrj
208*38fd1498Szrj key.vtable_decl = vtable_decl;
209*38fd1498Szrj slot = node->registered->find_slot (&key, INSERT);
210*38fd1498Szrj
211*38fd1498Szrj if (! *slot)
212*38fd1498Szrj {
213*38fd1498Szrj struct vtable_registration *node;
214*38fd1498Szrj node = XNEW (struct vtable_registration);
215*38fd1498Szrj node->vtable_decl = vtable_decl;
216*38fd1498Szrj
217*38fd1498Szrj (node->offsets).create (10);
218*38fd1498Szrj (node->offsets).safe_push (offset);
219*38fd1498Szrj *slot = node;
220*38fd1498Szrj inserted_something = true;
221*38fd1498Szrj }
222*38fd1498Szrj else
223*38fd1498Szrj {
224*38fd1498Szrj /* We found the vtable_decl slot; we need to see if it already
225*38fd1498Szrj contains the offset. If not, we need to add the offset. */
226*38fd1498Szrj unsigned i;
227*38fd1498Szrj bool found = false;
228*38fd1498Szrj for (i = 0; i < ((*slot)->offsets).length () && !found; ++i)
229*38fd1498Szrj if ((*slot)->offsets[i] == offset)
230*38fd1498Szrj found = true;
231*38fd1498Szrj
232*38fd1498Szrj if (!found)
233*38fd1498Szrj {
234*38fd1498Szrj ((*slot)->offsets).safe_push (offset);
235*38fd1498Szrj inserted_something = true;
236*38fd1498Szrj }
237*38fd1498Szrj }
238*38fd1498Szrj return inserted_something;
239*38fd1498Szrj }
240*38fd1498Szrj
241*38fd1498Szrj /* Hashtable functions for vtable_registration hashtables. */
242*38fd1498Szrj
243*38fd1498Szrj inline hashval_t
hash(const vtable_registration * p)244*38fd1498Szrj registration_hasher::hash (const vtable_registration *p)
245*38fd1498Szrj {
246*38fd1498Szrj const struct vtable_registration *n = (const struct vtable_registration *) p;
247*38fd1498Szrj return (hashval_t) (DECL_UID (n->vtable_decl));
248*38fd1498Szrj }
249*38fd1498Szrj
250*38fd1498Szrj inline bool
equal(const vtable_registration * p1,const vtable_registration * p2)251*38fd1498Szrj registration_hasher::equal (const vtable_registration *p1,
252*38fd1498Szrj const vtable_registration *p2)
253*38fd1498Szrj {
254*38fd1498Szrj const struct vtable_registration *n1 =
255*38fd1498Szrj (const struct vtable_registration *) p1;
256*38fd1498Szrj const struct vtable_registration *n2 =
257*38fd1498Szrj (const struct vtable_registration *) p2;
258*38fd1498Szrj return (DECL_UID (n1->vtable_decl) == DECL_UID (n2->vtable_decl));
259*38fd1498Szrj }
260*38fd1498Szrj
261*38fd1498Szrj /* End of hashtable functions for "registered" hashtables. */
262*38fd1498Szrj
263*38fd1498Szrj
264*38fd1498Szrj
265*38fd1498Szrj /* Hashtable definition and functions for vtbl_map_hash. */
266*38fd1498Szrj
267*38fd1498Szrj struct vtbl_map_hasher : nofree_ptr_hash <struct vtbl_map_node>
268*38fd1498Szrj {
269*38fd1498Szrj static inline hashval_t hash (const vtbl_map_node *);
270*38fd1498Szrj static inline bool equal (const vtbl_map_node *, const vtbl_map_node *);
271*38fd1498Szrj };
272*38fd1498Szrj
273*38fd1498Szrj /* Returns a hash code for P. */
274*38fd1498Szrj
275*38fd1498Szrj inline hashval_t
hash(const vtbl_map_node * p)276*38fd1498Szrj vtbl_map_hasher::hash (const vtbl_map_node *p)
277*38fd1498Szrj {
278*38fd1498Szrj const struct vtbl_map_node n = *((const struct vtbl_map_node *) p);
279*38fd1498Szrj return (hashval_t) IDENTIFIER_HASH_VALUE (n.class_name);
280*38fd1498Szrj }
281*38fd1498Szrj
282*38fd1498Szrj /* Returns nonzero if P1 and P2 are equal. */
283*38fd1498Szrj
284*38fd1498Szrj inline bool
equal(const vtbl_map_node * p1,const vtbl_map_node * p2)285*38fd1498Szrj vtbl_map_hasher::equal (const vtbl_map_node *p1, const vtbl_map_node *p2)
286*38fd1498Szrj {
287*38fd1498Szrj const struct vtbl_map_node n1 = *((const struct vtbl_map_node *) p1);
288*38fd1498Szrj const struct vtbl_map_node n2 = *((const struct vtbl_map_node *) p2);
289*38fd1498Szrj return (IDENTIFIER_HASH_VALUE (n1.class_name) ==
290*38fd1498Szrj IDENTIFIER_HASH_VALUE (n2.class_name));
291*38fd1498Szrj }
292*38fd1498Szrj
293*38fd1498Szrj /* Here are the two structures into which we insert vtable map nodes.
294*38fd1498Szrj We use two data structures because of the vastly different ways we need
295*38fd1498Szrj to find the nodes for various tasks (see comments in vtable-verify.h
296*38fd1498Szrj for more details. */
297*38fd1498Szrj
298*38fd1498Szrj typedef hash_table<vtbl_map_hasher> vtbl_map_table_type;
299*38fd1498Szrj typedef vtbl_map_table_type::iterator vtbl_map_iterator_type;
300*38fd1498Szrj
301*38fd1498Szrj /* Vtable map variable nodes stored in a hash table. */
302*38fd1498Szrj static vtbl_map_table_type *vtbl_map_hash;
303*38fd1498Szrj
304*38fd1498Szrj /* Vtable map variable nodes stored in a vector. */
305*38fd1498Szrj vec<struct vtbl_map_node *> vtbl_map_nodes_vec;
306*38fd1498Szrj
307*38fd1498Szrj /* Vector of mangled names for anonymous classes. */
308*38fd1498Szrj extern GTY(()) vec<tree, va_gc> *vtbl_mangled_name_types;
309*38fd1498Szrj extern GTY(()) vec<tree, va_gc> *vtbl_mangled_name_ids;
310*38fd1498Szrj vec<tree, va_gc> *vtbl_mangled_name_types;
311*38fd1498Szrj vec<tree, va_gc> *vtbl_mangled_name_ids;
312*38fd1498Szrj
313*38fd1498Szrj /* Look up class_type (a type decl for record types) in the vtbl_mangled_names_*
314*38fd1498Szrj vectors. This is a linear lookup. Return the associated mangled name for
315*38fd1498Szrj the class type. This is for handling types from anonymous namespaces, whose
316*38fd1498Szrj DECL_ASSEMBLER_NAME ends up being "<anon>", which is useless for our
317*38fd1498Szrj purposes.
318*38fd1498Szrj
319*38fd1498Szrj We use two vectors of trees to keep track of the mangled names: One is a
320*38fd1498Szrj vector of class types and the other is a vector of the mangled names. The
321*38fd1498Szrj assumption is that these two vectors are kept in perfect lock-step so that
322*38fd1498Szrj vtbl_mangled_name_ids[i] is the mangled name for
323*38fd1498Szrj vtbl_mangled_name_types[i]. */
324*38fd1498Szrj
325*38fd1498Szrj static tree
vtbl_find_mangled_name(tree class_type)326*38fd1498Szrj vtbl_find_mangled_name (tree class_type)
327*38fd1498Szrj {
328*38fd1498Szrj tree result = NULL_TREE;
329*38fd1498Szrj unsigned i;
330*38fd1498Szrj
331*38fd1498Szrj if (!vtbl_mangled_name_types or !vtbl_mangled_name_ids)
332*38fd1498Szrj return result;
333*38fd1498Szrj
334*38fd1498Szrj if (vtbl_mangled_name_types->length() != vtbl_mangled_name_ids->length())
335*38fd1498Szrj return result;
336*38fd1498Szrj
337*38fd1498Szrj for (i = 0; i < vtbl_mangled_name_types->length(); ++i)
338*38fd1498Szrj if ((*vtbl_mangled_name_types)[i] == class_type)
339*38fd1498Szrj {
340*38fd1498Szrj result = (*vtbl_mangled_name_ids)[i];
341*38fd1498Szrj break;
342*38fd1498Szrj }
343*38fd1498Szrj
344*38fd1498Szrj return result;
345*38fd1498Szrj }
346*38fd1498Szrj
347*38fd1498Szrj /* Store a class type decl and its mangled name, for an anonymous RECORD_TYPE,
348*38fd1498Szrj in the vtbl_mangled_names vector. Make sure there is not already an
349*38fd1498Szrj entry for the class type before adding it. */
350*38fd1498Szrj
351*38fd1498Szrj void
vtbl_register_mangled_name(tree class_type,tree mangled_name)352*38fd1498Szrj vtbl_register_mangled_name (tree class_type, tree mangled_name)
353*38fd1498Szrj {
354*38fd1498Szrj if (!vtbl_mangled_name_types)
355*38fd1498Szrj vec_alloc (vtbl_mangled_name_types, 10);
356*38fd1498Szrj
357*38fd1498Szrj if (!vtbl_mangled_name_ids)
358*38fd1498Szrj vec_alloc (vtbl_mangled_name_ids, 10);
359*38fd1498Szrj
360*38fd1498Szrj gcc_assert (vtbl_mangled_name_types->length() ==
361*38fd1498Szrj vtbl_mangled_name_ids->length());
362*38fd1498Szrj
363*38fd1498Szrj
364*38fd1498Szrj if (vtbl_find_mangled_name (class_type) == NULL_TREE)
365*38fd1498Szrj {
366*38fd1498Szrj vec_safe_push (vtbl_mangled_name_types, class_type);
367*38fd1498Szrj vec_safe_push (vtbl_mangled_name_ids, mangled_name);
368*38fd1498Szrj }
369*38fd1498Szrj }
370*38fd1498Szrj
371*38fd1498Szrj /* Return vtbl_map node for CLASS_NAME without creating a new one. */
372*38fd1498Szrj
373*38fd1498Szrj struct vtbl_map_node *
vtbl_map_get_node(tree class_type)374*38fd1498Szrj vtbl_map_get_node (tree class_type)
375*38fd1498Szrj {
376*38fd1498Szrj struct vtbl_map_node key;
377*38fd1498Szrj struct vtbl_map_node **slot;
378*38fd1498Szrj
379*38fd1498Szrj tree class_type_decl;
380*38fd1498Szrj tree class_name;
381*38fd1498Szrj unsigned int type_quals;
382*38fd1498Szrj
383*38fd1498Szrj if (!vtbl_map_hash)
384*38fd1498Szrj return NULL;
385*38fd1498Szrj
386*38fd1498Szrj gcc_assert (TREE_CODE (class_type) == RECORD_TYPE);
387*38fd1498Szrj
388*38fd1498Szrj
389*38fd1498Szrj /* Find the TYPE_DECL for the class. */
390*38fd1498Szrj class_type_decl = TYPE_NAME (class_type);
391*38fd1498Szrj
392*38fd1498Szrj /* Verify that there aren't any qualifiers on the type. */
393*38fd1498Szrj type_quals = TYPE_QUALS (TREE_TYPE (class_type_decl));
394*38fd1498Szrj gcc_assert (type_quals == TYPE_UNQUALIFIED);
395*38fd1498Szrj
396*38fd1498Szrj /* Get the mangled name for the unqualified type. */
397*38fd1498Szrj gcc_assert (HAS_DECL_ASSEMBLER_NAME_P (class_type_decl));
398*38fd1498Szrj class_name = DECL_ASSEMBLER_NAME (class_type_decl);
399*38fd1498Szrj
400*38fd1498Szrj if (strstr (IDENTIFIER_POINTER (class_name), "<anon>") != NULL)
401*38fd1498Szrj class_name = vtbl_find_mangled_name (class_type_decl);
402*38fd1498Szrj
403*38fd1498Szrj key.class_name = class_name;
404*38fd1498Szrj slot = (struct vtbl_map_node **) vtbl_map_hash->find_slot (&key, NO_INSERT);
405*38fd1498Szrj if (!slot)
406*38fd1498Szrj return NULL;
407*38fd1498Szrj return *slot;
408*38fd1498Szrj }
409*38fd1498Szrj
410*38fd1498Szrj /* Return vtbl_map node assigned to BASE_CLASS_TYPE. Create new one
411*38fd1498Szrj when needed. */
412*38fd1498Szrj
413*38fd1498Szrj struct vtbl_map_node *
find_or_create_vtbl_map_node(tree base_class_type)414*38fd1498Szrj find_or_create_vtbl_map_node (tree base_class_type)
415*38fd1498Szrj {
416*38fd1498Szrj struct vtbl_map_node key;
417*38fd1498Szrj struct vtbl_map_node *node;
418*38fd1498Szrj struct vtbl_map_node **slot;
419*38fd1498Szrj tree class_type_decl;
420*38fd1498Szrj unsigned int type_quals;
421*38fd1498Szrj
422*38fd1498Szrj if (!vtbl_map_hash)
423*38fd1498Szrj vtbl_map_hash = new vtbl_map_table_type (10);
424*38fd1498Szrj
425*38fd1498Szrj /* Find the TYPE_DECL for the class. */
426*38fd1498Szrj class_type_decl = TYPE_NAME (base_class_type);
427*38fd1498Szrj
428*38fd1498Szrj /* Verify that there aren't any type qualifiers on type. */
429*38fd1498Szrj type_quals = TYPE_QUALS (TREE_TYPE (class_type_decl));
430*38fd1498Szrj gcc_assert (type_quals == TYPE_UNQUALIFIED);
431*38fd1498Szrj
432*38fd1498Szrj gcc_assert (HAS_DECL_ASSEMBLER_NAME_P (class_type_decl));
433*38fd1498Szrj key.class_name = DECL_ASSEMBLER_NAME (class_type_decl);
434*38fd1498Szrj
435*38fd1498Szrj if (strstr (IDENTIFIER_POINTER (key.class_name), "<anon>") != NULL)
436*38fd1498Szrj key.class_name = vtbl_find_mangled_name (class_type_decl);
437*38fd1498Szrj
438*38fd1498Szrj slot = (struct vtbl_map_node **) vtbl_map_hash->find_slot (&key, INSERT);
439*38fd1498Szrj
440*38fd1498Szrj if (*slot)
441*38fd1498Szrj return *slot;
442*38fd1498Szrj
443*38fd1498Szrj node = XNEW (struct vtbl_map_node);
444*38fd1498Szrj node->vtbl_map_decl = NULL_TREE;
445*38fd1498Szrj node->class_name = key.class_name;
446*38fd1498Szrj node->uid = num_vtable_map_nodes++;
447*38fd1498Szrj
448*38fd1498Szrj node->class_info = XNEW (struct vtv_graph_node);
449*38fd1498Szrj node->class_info->class_type = base_class_type;
450*38fd1498Szrj node->class_info->class_uid = node->uid;
451*38fd1498Szrj node->class_info->num_processed_children = 0;
452*38fd1498Szrj
453*38fd1498Szrj (node->class_info->parents).create (4);
454*38fd1498Szrj (node->class_info->children).create (4);
455*38fd1498Szrj
456*38fd1498Szrj node->registered = new register_table_type (16);
457*38fd1498Szrj
458*38fd1498Szrj node->is_used = false;
459*38fd1498Szrj
460*38fd1498Szrj vtbl_map_nodes_vec.safe_push (node);
461*38fd1498Szrj gcc_assert (vtbl_map_nodes_vec[node->uid] == node);
462*38fd1498Szrj
463*38fd1498Szrj *slot = node;
464*38fd1498Szrj return node;
465*38fd1498Szrj }
466*38fd1498Szrj
467*38fd1498Szrj /* End of hashtable functions for vtable_map variables hash table. */
468*38fd1498Szrj
469*38fd1498Szrj /* Given a gimple STMT, this function checks to see if the statement
470*38fd1498Szrj is an assignment, the rhs of which is getting the vtable pointer
471*38fd1498Szrj value out of an object. (i.e. it's the value we need to verify
472*38fd1498Szrj because its the vtable pointer that will be used for a virtual
473*38fd1498Szrj call). */
474*38fd1498Szrj
475*38fd1498Szrj static bool
is_vtable_assignment_stmt(gimple * stmt)476*38fd1498Szrj is_vtable_assignment_stmt (gimple *stmt)
477*38fd1498Szrj {
478*38fd1498Szrj
479*38fd1498Szrj if (gimple_code (stmt) != GIMPLE_ASSIGN)
480*38fd1498Szrj return false;
481*38fd1498Szrj else
482*38fd1498Szrj {
483*38fd1498Szrj tree lhs = gimple_assign_lhs (stmt);
484*38fd1498Szrj tree rhs = gimple_assign_rhs1 (stmt);
485*38fd1498Szrj
486*38fd1498Szrj if (TREE_CODE (lhs) != SSA_NAME)
487*38fd1498Szrj return false;
488*38fd1498Szrj
489*38fd1498Szrj if (TREE_CODE (rhs) != COMPONENT_REF)
490*38fd1498Szrj return false;
491*38fd1498Szrj
492*38fd1498Szrj if (! (TREE_OPERAND (rhs, 1))
493*38fd1498Szrj || (TREE_CODE (TREE_OPERAND (rhs, 1)) != FIELD_DECL))
494*38fd1498Szrj return false;
495*38fd1498Szrj
496*38fd1498Szrj if (! DECL_VIRTUAL_P (TREE_OPERAND (rhs, 1)))
497*38fd1498Szrj return false;
498*38fd1498Szrj }
499*38fd1498Szrj
500*38fd1498Szrj return true;
501*38fd1498Szrj }
502*38fd1498Szrj
503*38fd1498Szrj /* This function attempts to recover the declared class of an object
504*38fd1498Szrj that is used in making a virtual call. We try to get the type from
505*38fd1498Szrj the type cast in the gimple assignment statement that extracts the
506*38fd1498Szrj vtable pointer from the object (DEF_STMT). The gimple statement
507*38fd1498Szrj usually looks something like this:
508*38fd1498Szrj
509*38fd1498Szrj D.2201_4 = MEM[(struct Event *)this_1(D)]._vptr.Event */
510*38fd1498Szrj
511*38fd1498Szrj static tree
extract_object_class_type(tree rhs)512*38fd1498Szrj extract_object_class_type (tree rhs)
513*38fd1498Szrj {
514*38fd1498Szrj tree result = NULL_TREE;
515*38fd1498Szrj
516*38fd1498Szrj /* Try to find and extract the type cast from that stmt. */
517*38fd1498Szrj if (TREE_CODE (rhs) == COMPONENT_REF)
518*38fd1498Szrj {
519*38fd1498Szrj tree op0 = TREE_OPERAND (rhs, 0);
520*38fd1498Szrj tree op1 = TREE_OPERAND (rhs, 1);
521*38fd1498Szrj
522*38fd1498Szrj if (TREE_CODE (op1) == FIELD_DECL
523*38fd1498Szrj && DECL_VIRTUAL_P (op1))
524*38fd1498Szrj {
525*38fd1498Szrj if (TREE_CODE (op0) == COMPONENT_REF
526*38fd1498Szrj && TREE_CODE (TREE_OPERAND (op0, 0)) == MEM_REF
527*38fd1498Szrj && TREE_CODE (TREE_TYPE (TREE_OPERAND (op0, 0)))== RECORD_TYPE)
528*38fd1498Szrj result = TREE_TYPE (TREE_OPERAND (op0, 0));
529*38fd1498Szrj else
530*38fd1498Szrj result = TREE_TYPE (op0);
531*38fd1498Szrj }
532*38fd1498Szrj else if (TREE_CODE (op0) == COMPONENT_REF)
533*38fd1498Szrj {
534*38fd1498Szrj result = extract_object_class_type (op0);
535*38fd1498Szrj if (result == NULL_TREE
536*38fd1498Szrj && TREE_CODE (op1) == COMPONENT_REF)
537*38fd1498Szrj result = extract_object_class_type (op1);
538*38fd1498Szrj }
539*38fd1498Szrj }
540*38fd1498Szrj
541*38fd1498Szrj return result;
542*38fd1498Szrj }
543*38fd1498Szrj
544*38fd1498Szrj /* This function traces forward through the def-use chain of an SSA
545*38fd1498Szrj variable to see if it ever gets used in a virtual function call. It
546*38fd1498Szrj returns a boolean indicating whether or not it found a virtual call in
547*38fd1498Szrj the use chain. */
548*38fd1498Szrj
549*38fd1498Szrj static bool
var_is_used_for_virtual_call_p(tree lhs,int * mem_ref_depth,int * recursion_depth)550*38fd1498Szrj var_is_used_for_virtual_call_p (tree lhs, int *mem_ref_depth,
551*38fd1498Szrj int *recursion_depth)
552*38fd1498Szrj {
553*38fd1498Szrj imm_use_iterator imm_iter;
554*38fd1498Szrj bool found_vcall = false;
555*38fd1498Szrj use_operand_p use_p;
556*38fd1498Szrj
557*38fd1498Szrj if (TREE_CODE (lhs) != SSA_NAME)
558*38fd1498Szrj return false;
559*38fd1498Szrj
560*38fd1498Szrj if (*mem_ref_depth > 2)
561*38fd1498Szrj return false;
562*38fd1498Szrj
563*38fd1498Szrj if (*recursion_depth > 25)
564*38fd1498Szrj /* If we've recursed this far the chances are pretty good that
565*38fd1498Szrj we're not going to find what we're looking for, and that we've
566*38fd1498Szrj gone down a recursion black hole. Time to stop. */
567*38fd1498Szrj return false;
568*38fd1498Szrj
569*38fd1498Szrj *recursion_depth = *recursion_depth + 1;
570*38fd1498Szrj
571*38fd1498Szrj /* Iterate through the immediate uses of the current variable. If
572*38fd1498Szrj it's a virtual function call, we're done. Otherwise, if there's
573*38fd1498Szrj an LHS for the use stmt, add the ssa var to the work list
574*38fd1498Szrj (assuming it's not already in the list and is not a variable
575*38fd1498Szrj we've already examined. */
576*38fd1498Szrj
577*38fd1498Szrj FOR_EACH_IMM_USE_FAST (use_p, imm_iter, lhs)
578*38fd1498Szrj {
579*38fd1498Szrj gimple *stmt2 = USE_STMT (use_p);
580*38fd1498Szrj
581*38fd1498Szrj if (is_gimple_call (stmt2))
582*38fd1498Szrj {
583*38fd1498Szrj tree fncall = gimple_call_fn (stmt2);
584*38fd1498Szrj if (fncall && TREE_CODE (fncall) == OBJ_TYPE_REF)
585*38fd1498Szrj found_vcall = true;
586*38fd1498Szrj else
587*38fd1498Szrj return false;
588*38fd1498Szrj }
589*38fd1498Szrj else if (gimple_code (stmt2) == GIMPLE_PHI)
590*38fd1498Szrj {
591*38fd1498Szrj found_vcall = var_is_used_for_virtual_call_p
592*38fd1498Szrj (gimple_phi_result (stmt2),
593*38fd1498Szrj mem_ref_depth,
594*38fd1498Szrj recursion_depth);
595*38fd1498Szrj }
596*38fd1498Szrj else if (is_gimple_assign (stmt2))
597*38fd1498Szrj {
598*38fd1498Szrj tree rhs = gimple_assign_rhs1 (stmt2);
599*38fd1498Szrj if (TREE_CODE (rhs) == ADDR_EXPR
600*38fd1498Szrj || TREE_CODE (rhs) == MEM_REF)
601*38fd1498Szrj *mem_ref_depth = *mem_ref_depth + 1;
602*38fd1498Szrj
603*38fd1498Szrj if (TREE_CODE (rhs) == COMPONENT_REF)
604*38fd1498Szrj {
605*38fd1498Szrj while (TREE_CODE (TREE_OPERAND (rhs, 0)) == COMPONENT_REF)
606*38fd1498Szrj rhs = TREE_OPERAND (rhs, 0);
607*38fd1498Szrj
608*38fd1498Szrj if (TREE_CODE (TREE_OPERAND (rhs, 0)) == ADDR_EXPR
609*38fd1498Szrj || TREE_CODE (TREE_OPERAND (rhs, 0)) == MEM_REF)
610*38fd1498Szrj *mem_ref_depth = *mem_ref_depth + 1;
611*38fd1498Szrj }
612*38fd1498Szrj
613*38fd1498Szrj if (*mem_ref_depth < 3)
614*38fd1498Szrj found_vcall = var_is_used_for_virtual_call_p
615*38fd1498Szrj (gimple_assign_lhs (stmt2),
616*38fd1498Szrj mem_ref_depth,
617*38fd1498Szrj recursion_depth);
618*38fd1498Szrj }
619*38fd1498Szrj
620*38fd1498Szrj else
621*38fd1498Szrj break;
622*38fd1498Szrj
623*38fd1498Szrj if (found_vcall)
624*38fd1498Szrj return true;
625*38fd1498Szrj }
626*38fd1498Szrj
627*38fd1498Szrj return false;
628*38fd1498Szrj }
629*38fd1498Szrj
630*38fd1498Szrj /* Search through all the statements in a basic block (BB), searching
631*38fd1498Szrj for virtual method calls. For each virtual method dispatch, find
632*38fd1498Szrj the vptr value used, and the statically declared type of the
633*38fd1498Szrj object; retrieve the vtable map variable for the type of the
634*38fd1498Szrj object; generate a call to __VLTVerifyVtablePointer; and insert the
635*38fd1498Szrj generated call into the basic block, after the point where the vptr
636*38fd1498Szrj value is gotten out of the object and before the virtual method
637*38fd1498Szrj dispatch. Make the virtual method dispatch depend on the return
638*38fd1498Szrj value from the verification call, so that subsequent optimizations
639*38fd1498Szrj cannot reorder the two calls. */
640*38fd1498Szrj
641*38fd1498Szrj static void
verify_bb_vtables(basic_block bb)642*38fd1498Szrj verify_bb_vtables (basic_block bb)
643*38fd1498Szrj {
644*38fd1498Szrj gimple_seq stmts;
645*38fd1498Szrj gimple *stmt = NULL;
646*38fd1498Szrj gimple_stmt_iterator gsi_vtbl_assign;
647*38fd1498Szrj gimple_stmt_iterator gsi_virtual_call;
648*38fd1498Szrj
649*38fd1498Szrj stmts = bb_seq (bb);
650*38fd1498Szrj gsi_virtual_call = gsi_start (stmts);
651*38fd1498Szrj for (; !gsi_end_p (gsi_virtual_call); gsi_next (&gsi_virtual_call))
652*38fd1498Szrj {
653*38fd1498Szrj stmt = gsi_stmt (gsi_virtual_call);
654*38fd1498Szrj
655*38fd1498Szrj /* Count virtual calls. */
656*38fd1498Szrj if (is_gimple_call (stmt))
657*38fd1498Szrj {
658*38fd1498Szrj tree fncall = gimple_call_fn (stmt);
659*38fd1498Szrj if (fncall && TREE_CODE (fncall) == OBJ_TYPE_REF)
660*38fd1498Szrj total_num_virtual_calls++;
661*38fd1498Szrj }
662*38fd1498Szrj
663*38fd1498Szrj if (is_vtable_assignment_stmt (stmt))
664*38fd1498Szrj {
665*38fd1498Szrj tree lhs = gimple_assign_lhs (stmt);
666*38fd1498Szrj tree vtbl_var_decl = NULL_TREE;
667*38fd1498Szrj struct vtbl_map_node *vtable_map_node;
668*38fd1498Szrj tree vtbl_decl = NULL_TREE;
669*38fd1498Szrj gcall *call_stmt;
670*38fd1498Szrj const char *vtable_name = "<unknown>";
671*38fd1498Szrj tree tmp0;
672*38fd1498Szrj bool found;
673*38fd1498Szrj int mem_ref_depth = 0;
674*38fd1498Szrj int recursion_depth = 0;
675*38fd1498Szrj
676*38fd1498Szrj /* Make sure this vptr field access is for a virtual call. */
677*38fd1498Szrj if (!var_is_used_for_virtual_call_p (lhs, &mem_ref_depth,
678*38fd1498Szrj &recursion_depth))
679*38fd1498Szrj continue;
680*38fd1498Szrj
681*38fd1498Szrj /* Now we have found the virtual method dispatch and
682*38fd1498Szrj the preceding access of the _vptr.* field... Next
683*38fd1498Szrj we need to find the statically declared type of
684*38fd1498Szrj the object, so we can find and use the right
685*38fd1498Szrj vtable map variable in the verification call. */
686*38fd1498Szrj tree class_type = extract_object_class_type
687*38fd1498Szrj (gimple_assign_rhs1 (stmt));
688*38fd1498Szrj
689*38fd1498Szrj gsi_vtbl_assign = gsi_for_stmt (stmt);
690*38fd1498Szrj
691*38fd1498Szrj if (class_type
692*38fd1498Szrj && (TREE_CODE (class_type) == RECORD_TYPE)
693*38fd1498Szrj && TYPE_BINFO (class_type))
694*38fd1498Szrj {
695*38fd1498Szrj /* Get the vtable VAR_DECL for the type. */
696*38fd1498Szrj vtbl_var_decl = BINFO_VTABLE (TYPE_BINFO (class_type));
697*38fd1498Szrj
698*38fd1498Szrj if (TREE_CODE (vtbl_var_decl) == POINTER_PLUS_EXPR)
699*38fd1498Szrj vtbl_var_decl = TREE_OPERAND (TREE_OPERAND (vtbl_var_decl, 0),
700*38fd1498Szrj 0);
701*38fd1498Szrj
702*38fd1498Szrj gcc_assert (vtbl_var_decl);
703*38fd1498Szrj
704*38fd1498Szrj vtbl_decl = vtbl_var_decl;
705*38fd1498Szrj vtable_map_node = vtbl_map_get_node
706*38fd1498Szrj (TYPE_MAIN_VARIANT (class_type));
707*38fd1498Szrj
708*38fd1498Szrj gcc_assert (verify_vtbl_ptr_fndecl);
709*38fd1498Szrj
710*38fd1498Szrj /* Given the vtable pointer for the base class of the
711*38fd1498Szrj object, build the call to __VLTVerifyVtablePointer to
712*38fd1498Szrj verify that the object's vtable pointer (contained in
713*38fd1498Szrj lhs) is in the set of valid vtable pointers for the
714*38fd1498Szrj base class. */
715*38fd1498Szrj
716*38fd1498Szrj if (vtable_map_node && vtable_map_node->vtbl_map_decl)
717*38fd1498Szrj {
718*38fd1498Szrj vtable_map_node->is_used = true;
719*38fd1498Szrj vtbl_var_decl = vtable_map_node->vtbl_map_decl;
720*38fd1498Szrj
721*38fd1498Szrj if (VAR_P (vtbl_decl))
722*38fd1498Szrj vtable_name = IDENTIFIER_POINTER (DECL_NAME (vtbl_decl));
723*38fd1498Szrj
724*38fd1498Szrj /* Call different routines if we are interested in
725*38fd1498Szrj trace information to debug problems. */
726*38fd1498Szrj if (flag_vtv_debug)
727*38fd1498Szrj {
728*38fd1498Szrj int len1 = IDENTIFIER_LENGTH
729*38fd1498Szrj (DECL_NAME (vtbl_var_decl));
730*38fd1498Szrj int len2 = strlen (vtable_name);
731*38fd1498Szrj
732*38fd1498Szrj call_stmt = gimple_build_call
733*38fd1498Szrj (verify_vtbl_ptr_fndecl, 4,
734*38fd1498Szrj build1 (ADDR_EXPR,
735*38fd1498Szrj TYPE_POINTER_TO
736*38fd1498Szrj (TREE_TYPE (vtbl_var_decl)),
737*38fd1498Szrj vtbl_var_decl),
738*38fd1498Szrj lhs,
739*38fd1498Szrj build_string_literal
740*38fd1498Szrj (len1 + 1,
741*38fd1498Szrj IDENTIFIER_POINTER
742*38fd1498Szrj (DECL_NAME
743*38fd1498Szrj (vtbl_var_decl))),
744*38fd1498Szrj build_string_literal (len2 + 1,
745*38fd1498Szrj vtable_name));
746*38fd1498Szrj }
747*38fd1498Szrj else
748*38fd1498Szrj call_stmt = gimple_build_call
749*38fd1498Szrj (verify_vtbl_ptr_fndecl, 2,
750*38fd1498Szrj build1 (ADDR_EXPR,
751*38fd1498Szrj TYPE_POINTER_TO
752*38fd1498Szrj (TREE_TYPE (vtbl_var_decl)),
753*38fd1498Szrj vtbl_var_decl),
754*38fd1498Szrj lhs);
755*38fd1498Szrj
756*38fd1498Szrj
757*38fd1498Szrj /* Create a new SSA_NAME var to hold the call's
758*38fd1498Szrj return value, and make the call_stmt use the
759*38fd1498Szrj variable for that purpose. */
760*38fd1498Szrj tmp0 = make_temp_ssa_name (TREE_TYPE (lhs), NULL, "VTV");
761*38fd1498Szrj gimple_call_set_lhs (call_stmt, tmp0);
762*38fd1498Szrj update_stmt (call_stmt);
763*38fd1498Szrj
764*38fd1498Szrj /* Replace all uses of lhs with tmp0. */
765*38fd1498Szrj found = false;
766*38fd1498Szrj imm_use_iterator iterator;
767*38fd1498Szrj gimple *use_stmt;
768*38fd1498Szrj FOR_EACH_IMM_USE_STMT (use_stmt, iterator, lhs)
769*38fd1498Szrj {
770*38fd1498Szrj use_operand_p use_p;
771*38fd1498Szrj if (use_stmt == call_stmt)
772*38fd1498Szrj continue;
773*38fd1498Szrj FOR_EACH_IMM_USE_ON_STMT (use_p, iterator)
774*38fd1498Szrj SET_USE (use_p, tmp0);
775*38fd1498Szrj update_stmt (use_stmt);
776*38fd1498Szrj found = true;
777*38fd1498Szrj }
778*38fd1498Szrj
779*38fd1498Szrj gcc_assert (found);
780*38fd1498Szrj
781*38fd1498Szrj /* Insert the new verification call just after the
782*38fd1498Szrj statement that gets the vtable pointer out of the
783*38fd1498Szrj object. */
784*38fd1498Szrj gcc_assert (gsi_stmt (gsi_vtbl_assign) == stmt);
785*38fd1498Szrj gsi_insert_after (&gsi_vtbl_assign, call_stmt,
786*38fd1498Szrj GSI_NEW_STMT);
787*38fd1498Szrj
788*38fd1498Szrj any_verification_calls_generated = true;
789*38fd1498Szrj total_num_verified_vcalls++;
790*38fd1498Szrj }
791*38fd1498Szrj }
792*38fd1498Szrj }
793*38fd1498Szrj }
794*38fd1498Szrj }
795*38fd1498Szrj
796*38fd1498Szrj /* Definition of this optimization pass. */
797*38fd1498Szrj
798*38fd1498Szrj namespace {
799*38fd1498Szrj
800*38fd1498Szrj const pass_data pass_data_vtable_verify =
801*38fd1498Szrj {
802*38fd1498Szrj GIMPLE_PASS, /* type */
803*38fd1498Szrj "vtable-verify", /* name */
804*38fd1498Szrj OPTGROUP_NONE, /* optinfo_flags */
805*38fd1498Szrj TV_VTABLE_VERIFICATION, /* tv_id */
806*38fd1498Szrj ( PROP_cfg | PROP_ssa ), /* properties_required */
807*38fd1498Szrj 0, /* properties_provided */
808*38fd1498Szrj 0, /* properties_destroyed */
809*38fd1498Szrj 0, /* todo_flags_start */
810*38fd1498Szrj TODO_update_ssa, /* todo_flags_finish */
811*38fd1498Szrj };
812*38fd1498Szrj
813*38fd1498Szrj class pass_vtable_verify : public gimple_opt_pass
814*38fd1498Szrj {
815*38fd1498Szrj public:
pass_vtable_verify(gcc::context * ctxt)816*38fd1498Szrj pass_vtable_verify (gcc::context *ctxt)
817*38fd1498Szrj : gimple_opt_pass (pass_data_vtable_verify, ctxt)
818*38fd1498Szrj {}
819*38fd1498Szrj
820*38fd1498Szrj /* opt_pass methods: */
gate(function *)821*38fd1498Szrj virtual bool gate (function *) { return (flag_vtable_verify); }
822*38fd1498Szrj virtual unsigned int execute (function *);
823*38fd1498Szrj
824*38fd1498Szrj }; // class pass_vtable_verify
825*38fd1498Szrj
826*38fd1498Szrj /* Loop through all the basic blocks in the current function, passing them to
827*38fd1498Szrj verify_bb_vtables, which searches for virtual calls, and inserts
828*38fd1498Szrj calls to __VLTVerifyVtablePointer. */
829*38fd1498Szrj
830*38fd1498Szrj unsigned int
execute(function * fun)831*38fd1498Szrj pass_vtable_verify::execute (function *fun)
832*38fd1498Szrj {
833*38fd1498Szrj unsigned int ret = 1;
834*38fd1498Szrj basic_block bb;
835*38fd1498Szrj
836*38fd1498Szrj FOR_ALL_BB_FN (bb, fun)
837*38fd1498Szrj verify_bb_vtables (bb);
838*38fd1498Szrj
839*38fd1498Szrj return ret;
840*38fd1498Szrj }
841*38fd1498Szrj
842*38fd1498Szrj } // anon namespace
843*38fd1498Szrj
844*38fd1498Szrj gimple_opt_pass *
make_pass_vtable_verify(gcc::context * ctxt)845*38fd1498Szrj make_pass_vtable_verify (gcc::context *ctxt)
846*38fd1498Szrj {
847*38fd1498Szrj return new pass_vtable_verify (ctxt);
848*38fd1498Szrj }
849*38fd1498Szrj
850*38fd1498Szrj #include "gt-vtable-verify.h"
851