PR c++/86171 - ICE with recursive alias instantiation.
[official-gcc.git] / gcc / var-tracking.c
blob2bbde92086fe8de195f2acdce37b5d5409cbd96b
1 /* Variable tracking routines for the GNU compiler.
2 Copyright (C) 2002-2018 Free Software Foundation, Inc.
4 This file is part of GCC.
6 GCC is free software; you can redistribute it and/or modify it
7 under the terms of the GNU General Public License as published by
8 the Free Software Foundation; either version 3, or (at your option)
9 any later version.
11 GCC is distributed in the hope that it will be useful, but WITHOUT
12 ANY WARRANTY; without even the implied warranty of MERCHANTABILITY
13 or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public
14 License for more details.
16 You should have received a copy of the GNU General Public License
17 along with GCC; see the file COPYING3. If not see
18 <http://www.gnu.org/licenses/>. */
20 /* This file contains the variable tracking pass. It computes where
21 variables are located (which registers or where in memory) at each position
22 in instruction stream and emits notes describing the locations.
23 Debug information (DWARF2 location lists) is finally generated from
24 these notes.
25 With this debug information, it is possible to show variables
26 even when debugging optimized code.
28 How does the variable tracking pass work?
30 First, it scans RTL code for uses, stores and clobbers (register/memory
31 references in instructions), for call insns and for stack adjustments
32 separately for each basic block and saves them to an array of micro
33 operations.
34 The micro operations of one instruction are ordered so that
35 pre-modifying stack adjustment < use < use with no var < call insn <
36 < clobber < set < post-modifying stack adjustment
38 Then, a forward dataflow analysis is performed to find out how locations
39 of variables change through code and to propagate the variable locations
40 along control flow graph.
41 The IN set for basic block BB is computed as a union of OUT sets of BB's
42 predecessors, the OUT set for BB is copied from the IN set for BB and
43 is changed according to micro operations in BB.
45 The IN and OUT sets for basic blocks consist of a current stack adjustment
46 (used for adjusting offset of variables addressed using stack pointer),
47 the table of structures describing the locations of parts of a variable
48 and for each physical register a linked list for each physical register.
49 The linked list is a list of variable parts stored in the register,
50 i.e. it is a list of triplets (reg, decl, offset) where decl is
51 REG_EXPR (reg) and offset is REG_OFFSET (reg). The linked list is used for
52 effective deleting appropriate variable parts when we set or clobber the
53 register.
55 There may be more than one variable part in a register. The linked lists
56 should be pretty short so it is a good data structure here.
57 For example in the following code, register allocator may assign same
58 register to variables A and B, and both of them are stored in the same
59 register in CODE:
61 if (cond)
62 set A;
63 else
64 set B;
65 CODE;
66 if (cond)
67 use A;
68 else
69 use B;
71 Finally, the NOTE_INSN_VAR_LOCATION notes describing the variable locations
72 are emitted to appropriate positions in RTL code. Each such a note describes
73 the location of one variable at the point in instruction stream where the
74 note is. There is no need to emit a note for each variable before each
75 instruction, we only emit these notes where the location of variable changes
76 (this means that we also emit notes for changes between the OUT set of the
77 previous block and the IN set of the current block).
79 The notes consist of two parts:
80 1. the declaration (from REG_EXPR or MEM_EXPR)
81 2. the location of a variable - it is either a simple register/memory
82 reference (for simple variables, for example int),
83 or a parallel of register/memory references (for a large variables
84 which consist of several parts, for example long long).
88 #include "config.h"
89 #include "system.h"
90 #include "coretypes.h"
91 #include "backend.h"
92 #include "target.h"
93 #include "rtl.h"
94 #include "tree.h"
95 #include "cfghooks.h"
96 #include "alloc-pool.h"
97 #include "tree-pass.h"
98 #include "memmodel.h"
99 #include "tm_p.h"
100 #include "insn-config.h"
101 #include "regs.h"
102 #include "emit-rtl.h"
103 #include "recog.h"
104 #include "diagnostic.h"
105 #include "varasm.h"
106 #include "stor-layout.h"
107 #include "cfgrtl.h"
108 #include "cfganal.h"
109 #include "reload.h"
110 #include "calls.h"
111 #include "tree-dfa.h"
112 #include "tree-ssa.h"
113 #include "cselib.h"
114 #include "params.h"
115 #include "tree-pretty-print.h"
116 #include "rtl-iter.h"
117 #include "fibonacci_heap.h"
119 typedef fibonacci_heap <long, basic_block_def> bb_heap_t;
120 typedef fibonacci_node <long, basic_block_def> bb_heap_node_t;
122 /* var-tracking.c assumes that tree code with the same value as VALUE rtx code
123 has no chance to appear in REG_EXPR/MEM_EXPRs and isn't a decl.
124 Currently the value is the same as IDENTIFIER_NODE, which has such
125 a property. If this compile time assertion ever fails, make sure that
126 the new tree code that equals (int) VALUE has the same property. */
127 extern char check_value_val[(int) VALUE == (int) IDENTIFIER_NODE ? 1 : -1];
129 /* Type of micro operation. */
130 enum micro_operation_type
132 MO_USE, /* Use location (REG or MEM). */
133 MO_USE_NO_VAR,/* Use location which is not associated with a variable
134 or the variable is not trackable. */
135 MO_VAL_USE, /* Use location which is associated with a value. */
136 MO_VAL_LOC, /* Use location which appears in a debug insn. */
137 MO_VAL_SET, /* Set location associated with a value. */
138 MO_SET, /* Set location. */
139 MO_COPY, /* Copy the same portion of a variable from one
140 location to another. */
141 MO_CLOBBER, /* Clobber location. */
142 MO_CALL, /* Call insn. */
143 MO_ADJUST /* Adjust stack pointer. */
147 static const char * const ATTRIBUTE_UNUSED
148 micro_operation_type_name[] = {
149 "MO_USE",
150 "MO_USE_NO_VAR",
151 "MO_VAL_USE",
152 "MO_VAL_LOC",
153 "MO_VAL_SET",
154 "MO_SET",
155 "MO_COPY",
156 "MO_CLOBBER",
157 "MO_CALL",
158 "MO_ADJUST"
161 /* Where shall the note be emitted? BEFORE or AFTER the instruction.
162 Notes emitted as AFTER_CALL are to take effect during the call,
163 rather than after the call. */
164 enum emit_note_where
166 EMIT_NOTE_BEFORE_INSN,
167 EMIT_NOTE_AFTER_INSN,
168 EMIT_NOTE_AFTER_CALL_INSN
171 /* Structure holding information about micro operation. */
172 struct micro_operation
174 /* Type of micro operation. */
175 enum micro_operation_type type;
177 /* The instruction which the micro operation is in, for MO_USE,
178 MO_USE_NO_VAR, MO_CALL and MO_ADJUST, or the subsequent
179 instruction or note in the original flow (before any var-tracking
180 notes are inserted, to simplify emission of notes), for MO_SET
181 and MO_CLOBBER. */
182 rtx_insn *insn;
184 union {
185 /* Location. For MO_SET and MO_COPY, this is the SET that
186 performs the assignment, if known, otherwise it is the target
187 of the assignment. For MO_VAL_USE and MO_VAL_SET, it is a
188 CONCAT of the VALUE and the LOC associated with it. For
189 MO_VAL_LOC, it is a CONCAT of the VALUE and the VAR_LOCATION
190 associated with it. */
191 rtx loc;
193 /* Stack adjustment. */
194 HOST_WIDE_INT adjust;
195 } u;
199 /* A declaration of a variable, or an RTL value being handled like a
200 declaration. */
201 typedef void *decl_or_value;
203 /* Return true if a decl_or_value DV is a DECL or NULL. */
204 static inline bool
205 dv_is_decl_p (decl_or_value dv)
207 return !dv || (int) TREE_CODE ((tree) dv) != (int) VALUE;
210 /* Return true if a decl_or_value is a VALUE rtl. */
211 static inline bool
212 dv_is_value_p (decl_or_value dv)
214 return dv && !dv_is_decl_p (dv);
217 /* Return the decl in the decl_or_value. */
218 static inline tree
219 dv_as_decl (decl_or_value dv)
221 gcc_checking_assert (dv_is_decl_p (dv));
222 return (tree) dv;
225 /* Return the value in the decl_or_value. */
226 static inline rtx
227 dv_as_value (decl_or_value dv)
229 gcc_checking_assert (dv_is_value_p (dv));
230 return (rtx)dv;
233 /* Return the opaque pointer in the decl_or_value. */
234 static inline void *
235 dv_as_opaque (decl_or_value dv)
237 return dv;
241 /* Description of location of a part of a variable. The content of a physical
242 register is described by a chain of these structures.
243 The chains are pretty short (usually 1 or 2 elements) and thus
244 chain is the best data structure. */
245 struct attrs
247 /* Pointer to next member of the list. */
248 attrs *next;
250 /* The rtx of register. */
251 rtx loc;
253 /* The declaration corresponding to LOC. */
254 decl_or_value dv;
256 /* Offset from start of DECL. */
257 HOST_WIDE_INT offset;
260 /* Structure for chaining the locations. */
261 struct location_chain
263 /* Next element in the chain. */
264 location_chain *next;
266 /* The location (REG, MEM or VALUE). */
267 rtx loc;
269 /* The "value" stored in this location. */
270 rtx set_src;
272 /* Initialized? */
273 enum var_init_status init;
276 /* A vector of loc_exp_dep holds the active dependencies of a one-part
277 DV on VALUEs, i.e., the VALUEs expanded so as to form the current
278 location of DV. Each entry is also part of VALUE' s linked-list of
279 backlinks back to DV. */
280 struct loc_exp_dep
282 /* The dependent DV. */
283 decl_or_value dv;
284 /* The dependency VALUE or DECL_DEBUG. */
285 rtx value;
286 /* The next entry in VALUE's backlinks list. */
287 struct loc_exp_dep *next;
288 /* A pointer to the pointer to this entry (head or prev's next) in
289 the doubly-linked list. */
290 struct loc_exp_dep **pprev;
294 /* This data structure holds information about the depth of a variable
295 expansion. */
296 struct expand_depth
298 /* This measures the complexity of the expanded expression. It
299 grows by one for each level of expansion that adds more than one
300 operand. */
301 int complexity;
302 /* This counts the number of ENTRY_VALUE expressions in an
303 expansion. We want to minimize their use. */
304 int entryvals;
307 /* This data structure is allocated for one-part variables at the time
308 of emitting notes. */
309 struct onepart_aux
311 /* Doubly-linked list of dependent DVs. These are DVs whose cur_loc
312 computation used the expansion of this variable, and that ought
313 to be notified should this variable change. If the DV's cur_loc
314 expanded to NULL, all components of the loc list are regarded as
315 active, so that any changes in them give us a chance to get a
316 location. Otherwise, only components of the loc that expanded to
317 non-NULL are regarded as active dependencies. */
318 loc_exp_dep *backlinks;
319 /* This holds the LOC that was expanded into cur_loc. We need only
320 mark a one-part variable as changed if the FROM loc is removed,
321 or if it has no known location and a loc is added, or if it gets
322 a change notification from any of its active dependencies. */
323 rtx from;
324 /* The depth of the cur_loc expression. */
325 expand_depth depth;
326 /* Dependencies actively used when expand FROM into cur_loc. */
327 vec<loc_exp_dep, va_heap, vl_embed> deps;
330 /* Structure describing one part of variable. */
331 struct variable_part
333 /* Chain of locations of the part. */
334 location_chain *loc_chain;
336 /* Location which was last emitted to location list. */
337 rtx cur_loc;
339 union variable_aux
341 /* The offset in the variable, if !var->onepart. */
342 HOST_WIDE_INT offset;
344 /* Pointer to auxiliary data, if var->onepart and emit_notes. */
345 struct onepart_aux *onepaux;
346 } aux;
349 /* Maximum number of location parts. */
350 #define MAX_VAR_PARTS 16
352 /* Enumeration type used to discriminate various types of one-part
353 variables. */
354 enum onepart_enum
356 /* Not a one-part variable. */
357 NOT_ONEPART = 0,
358 /* A one-part DECL that is not a DEBUG_EXPR_DECL. */
359 ONEPART_VDECL = 1,
360 /* A DEBUG_EXPR_DECL. */
361 ONEPART_DEXPR = 2,
362 /* A VALUE. */
363 ONEPART_VALUE = 3
366 /* Structure describing where the variable is located. */
367 struct variable
369 /* The declaration of the variable, or an RTL value being handled
370 like a declaration. */
371 decl_or_value dv;
373 /* Reference count. */
374 int refcount;
376 /* Number of variable parts. */
377 char n_var_parts;
379 /* What type of DV this is, according to enum onepart_enum. */
380 ENUM_BITFIELD (onepart_enum) onepart : CHAR_BIT;
382 /* True if this variable_def struct is currently in the
383 changed_variables hash table. */
384 bool in_changed_variables;
386 /* The variable parts. */
387 variable_part var_part[1];
390 /* Pointer to the BB's information specific to variable tracking pass. */
391 #define VTI(BB) ((variable_tracking_info *) (BB)->aux)
393 /* Return MEM_OFFSET (MEM) as a HOST_WIDE_INT, or 0 if we can't. */
395 static inline HOST_WIDE_INT
396 int_mem_offset (const_rtx mem)
398 HOST_WIDE_INT offset;
399 if (MEM_OFFSET_KNOWN_P (mem) && MEM_OFFSET (mem).is_constant (&offset))
400 return offset;
401 return 0;
404 #if CHECKING_P && (GCC_VERSION >= 2007)
406 /* Access VAR's Ith part's offset, checking that it's not a one-part
407 variable. */
408 #define VAR_PART_OFFSET(var, i) __extension__ \
409 (*({ variable *const __v = (var); \
410 gcc_checking_assert (!__v->onepart); \
411 &__v->var_part[(i)].aux.offset; }))
413 /* Access VAR's one-part auxiliary data, checking that it is a
414 one-part variable. */
415 #define VAR_LOC_1PAUX(var) __extension__ \
416 (*({ variable *const __v = (var); \
417 gcc_checking_assert (__v->onepart); \
418 &__v->var_part[0].aux.onepaux; }))
420 #else
421 #define VAR_PART_OFFSET(var, i) ((var)->var_part[(i)].aux.offset)
422 #define VAR_LOC_1PAUX(var) ((var)->var_part[0].aux.onepaux)
423 #endif
425 /* These are accessor macros for the one-part auxiliary data. When
426 convenient for users, they're guarded by tests that the data was
427 allocated. */
428 #define VAR_LOC_DEP_LST(var) (VAR_LOC_1PAUX (var) \
429 ? VAR_LOC_1PAUX (var)->backlinks \
430 : NULL)
431 #define VAR_LOC_DEP_LSTP(var) (VAR_LOC_1PAUX (var) \
432 ? &VAR_LOC_1PAUX (var)->backlinks \
433 : NULL)
434 #define VAR_LOC_FROM(var) (VAR_LOC_1PAUX (var)->from)
435 #define VAR_LOC_DEPTH(var) (VAR_LOC_1PAUX (var)->depth)
436 #define VAR_LOC_DEP_VEC(var) (VAR_LOC_1PAUX (var) \
437 ? &VAR_LOC_1PAUX (var)->deps \
438 : NULL)
442 typedef unsigned int dvuid;
444 /* Return the uid of DV. */
446 static inline dvuid
447 dv_uid (decl_or_value dv)
449 if (dv_is_value_p (dv))
450 return CSELIB_VAL_PTR (dv_as_value (dv))->uid;
451 else
452 return DECL_UID (dv_as_decl (dv));
455 /* Compute the hash from the uid. */
457 static inline hashval_t
458 dv_uid2hash (dvuid uid)
460 return uid;
463 /* The hash function for a mask table in a shared_htab chain. */
465 static inline hashval_t
466 dv_htab_hash (decl_or_value dv)
468 return dv_uid2hash (dv_uid (dv));
471 static void variable_htab_free (void *);
473 /* Variable hashtable helpers. */
475 struct variable_hasher : pointer_hash <variable>
477 typedef void *compare_type;
478 static inline hashval_t hash (const variable *);
479 static inline bool equal (const variable *, const void *);
480 static inline void remove (variable *);
483 /* The hash function for variable_htab, computes the hash value
484 from the declaration of variable X. */
486 inline hashval_t
487 variable_hasher::hash (const variable *v)
489 return dv_htab_hash (v->dv);
492 /* Compare the declaration of variable X with declaration Y. */
494 inline bool
495 variable_hasher::equal (const variable *v, const void *y)
497 decl_or_value dv = CONST_CAST2 (decl_or_value, const void *, y);
499 return (dv_as_opaque (v->dv) == dv_as_opaque (dv));
502 /* Free the element of VARIABLE_HTAB (its type is struct variable_def). */
504 inline void
505 variable_hasher::remove (variable *var)
507 variable_htab_free (var);
510 typedef hash_table<variable_hasher> variable_table_type;
511 typedef variable_table_type::iterator variable_iterator_type;
513 /* Structure for passing some other parameters to function
514 emit_note_insn_var_location. */
515 struct emit_note_data
517 /* The instruction which the note will be emitted before/after. */
518 rtx_insn *insn;
520 /* Where the note will be emitted (before/after insn)? */
521 enum emit_note_where where;
523 /* The variables and values active at this point. */
524 variable_table_type *vars;
527 /* Structure holding a refcounted hash table. If refcount > 1,
528 it must be first unshared before modified. */
529 struct shared_hash
531 /* Reference count. */
532 int refcount;
534 /* Actual hash table. */
535 variable_table_type *htab;
538 /* Structure holding the IN or OUT set for a basic block. */
539 struct dataflow_set
541 /* Adjustment of stack offset. */
542 HOST_WIDE_INT stack_adjust;
544 /* Attributes for registers (lists of attrs). */
545 attrs *regs[FIRST_PSEUDO_REGISTER];
547 /* Variable locations. */
548 shared_hash *vars;
550 /* Vars that is being traversed. */
551 shared_hash *traversed_vars;
554 /* The structure (one for each basic block) containing the information
555 needed for variable tracking. */
556 struct variable_tracking_info
558 /* The vector of micro operations. */
559 vec<micro_operation> mos;
561 /* The IN and OUT set for dataflow analysis. */
562 dataflow_set in;
563 dataflow_set out;
565 /* The permanent-in dataflow set for this block. This is used to
566 hold values for which we had to compute entry values. ??? This
567 should probably be dynamically allocated, to avoid using more
568 memory in non-debug builds. */
569 dataflow_set *permp;
571 /* Has the block been visited in DFS? */
572 bool visited;
574 /* Has the block been flooded in VTA? */
575 bool flooded;
579 /* Alloc pool for struct attrs_def. */
580 object_allocator<attrs> attrs_pool ("attrs pool");
582 /* Alloc pool for struct variable_def with MAX_VAR_PARTS entries. */
584 static pool_allocator var_pool
585 ("variable_def pool", sizeof (variable) +
586 (MAX_VAR_PARTS - 1) * sizeof (((variable *)NULL)->var_part[0]));
588 /* Alloc pool for struct variable_def with a single var_part entry. */
589 static pool_allocator valvar_pool
590 ("small variable_def pool", sizeof (variable));
592 /* Alloc pool for struct location_chain. */
593 static object_allocator<location_chain> location_chain_pool
594 ("location_chain pool");
596 /* Alloc pool for struct shared_hash. */
597 static object_allocator<shared_hash> shared_hash_pool ("shared_hash pool");
599 /* Alloc pool for struct loc_exp_dep_s for NOT_ONEPART variables. */
600 object_allocator<loc_exp_dep> loc_exp_dep_pool ("loc_exp_dep pool");
602 /* Changed variables, notes will be emitted for them. */
603 static variable_table_type *changed_variables;
605 /* Shall notes be emitted? */
606 static bool emit_notes;
608 /* Values whose dynamic location lists have gone empty, but whose
609 cselib location lists are still usable. Use this to hold the
610 current location, the backlinks, etc, during emit_notes. */
611 static variable_table_type *dropped_values;
613 /* Empty shared hashtable. */
614 static shared_hash *empty_shared_hash;
616 /* Scratch register bitmap used by cselib_expand_value_rtx. */
617 static bitmap scratch_regs = NULL;
619 #ifdef HAVE_window_save
620 struct GTY(()) parm_reg {
621 rtx outgoing;
622 rtx incoming;
626 /* Vector of windowed parameter registers, if any. */
627 static vec<parm_reg, va_gc> *windowed_parm_regs = NULL;
628 #endif
630 /* Variable used to tell whether cselib_process_insn called our hook. */
631 static bool cselib_hook_called;
633 /* Local function prototypes. */
634 static void stack_adjust_offset_pre_post (rtx, HOST_WIDE_INT *,
635 HOST_WIDE_INT *);
636 static void insn_stack_adjust_offset_pre_post (rtx_insn *, HOST_WIDE_INT *,
637 HOST_WIDE_INT *);
638 static bool vt_stack_adjustments (void);
640 static void init_attrs_list_set (attrs **);
641 static void attrs_list_clear (attrs **);
642 static attrs *attrs_list_member (attrs *, decl_or_value, HOST_WIDE_INT);
643 static void attrs_list_insert (attrs **, decl_or_value, HOST_WIDE_INT, rtx);
644 static void attrs_list_copy (attrs **, attrs *);
645 static void attrs_list_union (attrs **, attrs *);
647 static variable **unshare_variable (dataflow_set *set, variable **slot,
648 variable *var, enum var_init_status);
649 static void vars_copy (variable_table_type *, variable_table_type *);
650 static tree var_debug_decl (tree);
651 static void var_reg_set (dataflow_set *, rtx, enum var_init_status, rtx);
652 static void var_reg_delete_and_set (dataflow_set *, rtx, bool,
653 enum var_init_status, rtx);
654 static void var_reg_delete (dataflow_set *, rtx, bool);
655 static void var_regno_delete (dataflow_set *, int);
656 static void var_mem_set (dataflow_set *, rtx, enum var_init_status, rtx);
657 static void var_mem_delete_and_set (dataflow_set *, rtx, bool,
658 enum var_init_status, rtx);
659 static void var_mem_delete (dataflow_set *, rtx, bool);
661 static void dataflow_set_init (dataflow_set *);
662 static void dataflow_set_clear (dataflow_set *);
663 static void dataflow_set_copy (dataflow_set *, dataflow_set *);
664 static int variable_union_info_cmp_pos (const void *, const void *);
665 static void dataflow_set_union (dataflow_set *, dataflow_set *);
666 static location_chain *find_loc_in_1pdv (rtx, variable *,
667 variable_table_type *);
668 static bool canon_value_cmp (rtx, rtx);
669 static int loc_cmp (rtx, rtx);
670 static bool variable_part_different_p (variable_part *, variable_part *);
671 static bool onepart_variable_different_p (variable *, variable *);
672 static bool variable_different_p (variable *, variable *);
673 static bool dataflow_set_different (dataflow_set *, dataflow_set *);
674 static void dataflow_set_destroy (dataflow_set *);
676 static bool track_expr_p (tree, bool);
677 static void add_uses_1 (rtx *, void *);
678 static void add_stores (rtx, const_rtx, void *);
679 static bool compute_bb_dataflow (basic_block);
680 static bool vt_find_locations (void);
682 static void dump_attrs_list (attrs *);
683 static void dump_var (variable *);
684 static void dump_vars (variable_table_type *);
685 static void dump_dataflow_set (dataflow_set *);
686 static void dump_dataflow_sets (void);
688 static void set_dv_changed (decl_or_value, bool);
689 static void variable_was_changed (variable *, dataflow_set *);
690 static variable **set_slot_part (dataflow_set *, rtx, variable **,
691 decl_or_value, HOST_WIDE_INT,
692 enum var_init_status, rtx);
693 static void set_variable_part (dataflow_set *, rtx,
694 decl_or_value, HOST_WIDE_INT,
695 enum var_init_status, rtx, enum insert_option);
696 static variable **clobber_slot_part (dataflow_set *, rtx,
697 variable **, HOST_WIDE_INT, rtx);
698 static void clobber_variable_part (dataflow_set *, rtx,
699 decl_or_value, HOST_WIDE_INT, rtx);
700 static variable **delete_slot_part (dataflow_set *, rtx, variable **,
701 HOST_WIDE_INT);
702 static void delete_variable_part (dataflow_set *, rtx,
703 decl_or_value, HOST_WIDE_INT);
704 static void emit_notes_in_bb (basic_block, dataflow_set *);
705 static void vt_emit_notes (void);
707 static void vt_add_function_parameters (void);
708 static bool vt_initialize (void);
709 static void vt_finalize (void);
711 /* Callback for stack_adjust_offset_pre_post, called via for_each_inc_dec. */
713 static int
714 stack_adjust_offset_pre_post_cb (rtx, rtx op, rtx dest, rtx src, rtx srcoff,
715 void *arg)
717 if (dest != stack_pointer_rtx)
718 return 0;
720 switch (GET_CODE (op))
722 case PRE_INC:
723 case PRE_DEC:
724 ((HOST_WIDE_INT *)arg)[0] -= INTVAL (srcoff);
725 return 0;
726 case POST_INC:
727 case POST_DEC:
728 ((HOST_WIDE_INT *)arg)[1] -= INTVAL (srcoff);
729 return 0;
730 case PRE_MODIFY:
731 case POST_MODIFY:
732 /* We handle only adjustments by constant amount. */
733 gcc_assert (GET_CODE (src) == PLUS
734 && CONST_INT_P (XEXP (src, 1))
735 && XEXP (src, 0) == stack_pointer_rtx);
736 ((HOST_WIDE_INT *)arg)[GET_CODE (op) == POST_MODIFY]
737 -= INTVAL (XEXP (src, 1));
738 return 0;
739 default:
740 gcc_unreachable ();
744 /* Given a SET, calculate the amount of stack adjustment it contains
745 PRE- and POST-modifying stack pointer.
746 This function is similar to stack_adjust_offset. */
748 static void
749 stack_adjust_offset_pre_post (rtx pattern, HOST_WIDE_INT *pre,
750 HOST_WIDE_INT *post)
752 rtx src = SET_SRC (pattern);
753 rtx dest = SET_DEST (pattern);
754 enum rtx_code code;
756 if (dest == stack_pointer_rtx)
758 /* (set (reg sp) (plus (reg sp) (const_int))) */
759 code = GET_CODE (src);
760 if (! (code == PLUS || code == MINUS)
761 || XEXP (src, 0) != stack_pointer_rtx
762 || !CONST_INT_P (XEXP (src, 1)))
763 return;
765 if (code == MINUS)
766 *post += INTVAL (XEXP (src, 1));
767 else
768 *post -= INTVAL (XEXP (src, 1));
769 return;
771 HOST_WIDE_INT res[2] = { 0, 0 };
772 for_each_inc_dec (pattern, stack_adjust_offset_pre_post_cb, res);
773 *pre += res[0];
774 *post += res[1];
777 /* Given an INSN, calculate the amount of stack adjustment it contains
778 PRE- and POST-modifying stack pointer. */
780 static void
781 insn_stack_adjust_offset_pre_post (rtx_insn *insn, HOST_WIDE_INT *pre,
782 HOST_WIDE_INT *post)
784 rtx pattern;
786 *pre = 0;
787 *post = 0;
789 pattern = PATTERN (insn);
790 if (RTX_FRAME_RELATED_P (insn))
792 rtx expr = find_reg_note (insn, REG_FRAME_RELATED_EXPR, NULL_RTX);
793 if (expr)
794 pattern = XEXP (expr, 0);
797 if (GET_CODE (pattern) == SET)
798 stack_adjust_offset_pre_post (pattern, pre, post);
799 else if (GET_CODE (pattern) == PARALLEL
800 || GET_CODE (pattern) == SEQUENCE)
802 int i;
804 /* There may be stack adjustments inside compound insns. Search
805 for them. */
806 for ( i = XVECLEN (pattern, 0) - 1; i >= 0; i--)
807 if (GET_CODE (XVECEXP (pattern, 0, i)) == SET)
808 stack_adjust_offset_pre_post (XVECEXP (pattern, 0, i), pre, post);
812 /* Compute stack adjustments for all blocks by traversing DFS tree.
813 Return true when the adjustments on all incoming edges are consistent.
814 Heavily borrowed from pre_and_rev_post_order_compute. */
816 static bool
817 vt_stack_adjustments (void)
819 edge_iterator *stack;
820 int sp;
822 /* Initialize entry block. */
823 VTI (ENTRY_BLOCK_PTR_FOR_FN (cfun))->visited = true;
824 VTI (ENTRY_BLOCK_PTR_FOR_FN (cfun))->in.stack_adjust
825 = INCOMING_FRAME_SP_OFFSET;
826 VTI (ENTRY_BLOCK_PTR_FOR_FN (cfun))->out.stack_adjust
827 = INCOMING_FRAME_SP_OFFSET;
829 /* Allocate stack for back-tracking up CFG. */
830 stack = XNEWVEC (edge_iterator, n_basic_blocks_for_fn (cfun) + 1);
831 sp = 0;
833 /* Push the first edge on to the stack. */
834 stack[sp++] = ei_start (ENTRY_BLOCK_PTR_FOR_FN (cfun)->succs);
836 while (sp)
838 edge_iterator ei;
839 basic_block src;
840 basic_block dest;
842 /* Look at the edge on the top of the stack. */
843 ei = stack[sp - 1];
844 src = ei_edge (ei)->src;
845 dest = ei_edge (ei)->dest;
847 /* Check if the edge destination has been visited yet. */
848 if (!VTI (dest)->visited)
850 rtx_insn *insn;
851 HOST_WIDE_INT pre, post, offset;
852 VTI (dest)->visited = true;
853 VTI (dest)->in.stack_adjust = offset = VTI (src)->out.stack_adjust;
855 if (dest != EXIT_BLOCK_PTR_FOR_FN (cfun))
856 for (insn = BB_HEAD (dest);
857 insn != NEXT_INSN (BB_END (dest));
858 insn = NEXT_INSN (insn))
859 if (INSN_P (insn))
861 insn_stack_adjust_offset_pre_post (insn, &pre, &post);
862 offset += pre + post;
865 VTI (dest)->out.stack_adjust = offset;
867 if (EDGE_COUNT (dest->succs) > 0)
868 /* Since the DEST node has been visited for the first
869 time, check its successors. */
870 stack[sp++] = ei_start (dest->succs);
872 else
874 /* We can end up with different stack adjustments for the exit block
875 of a shrink-wrapped function if stack_adjust_offset_pre_post
876 doesn't understand the rtx pattern used to restore the stack
877 pointer in the epilogue. For example, on s390(x), the stack
878 pointer is often restored via a load-multiple instruction
879 and so no stack_adjust offset is recorded for it. This means
880 that the stack offset at the end of the epilogue block is the
881 same as the offset before the epilogue, whereas other paths
882 to the exit block will have the correct stack_adjust.
884 It is safe to ignore these differences because (a) we never
885 use the stack_adjust for the exit block in this pass and
886 (b) dwarf2cfi checks whether the CFA notes in a shrink-wrapped
887 function are correct.
889 We must check whether the adjustments on other edges are
890 the same though. */
891 if (dest != EXIT_BLOCK_PTR_FOR_FN (cfun)
892 && VTI (dest)->in.stack_adjust != VTI (src)->out.stack_adjust)
894 free (stack);
895 return false;
898 if (! ei_one_before_end_p (ei))
899 /* Go to the next edge. */
900 ei_next (&stack[sp - 1]);
901 else
902 /* Return to previous level if there are no more edges. */
903 sp--;
907 free (stack);
908 return true;
911 /* arg_pointer_rtx resp. frame_pointer_rtx if stack_pointer_rtx or
912 hard_frame_pointer_rtx is being mapped to it and offset for it. */
913 static rtx cfa_base_rtx;
914 static HOST_WIDE_INT cfa_base_offset;
916 /* Compute a CFA-based value for an ADJUSTMENT made to stack_pointer_rtx
917 or hard_frame_pointer_rtx. */
919 static inline rtx
920 compute_cfa_pointer (poly_int64 adjustment)
922 return plus_constant (Pmode, cfa_base_rtx, adjustment + cfa_base_offset);
925 /* Adjustment for hard_frame_pointer_rtx to cfa base reg,
926 or -1 if the replacement shouldn't be done. */
927 static poly_int64 hard_frame_pointer_adjustment = -1;
929 /* Data for adjust_mems callback. */
931 struct adjust_mem_data
933 bool store;
934 machine_mode mem_mode;
935 HOST_WIDE_INT stack_adjust;
936 auto_vec<rtx> side_effects;
939 /* Helper for adjust_mems. Return true if X is suitable for
940 transformation of wider mode arithmetics to narrower mode. */
942 static bool
943 use_narrower_mode_test (rtx x, const_rtx subreg)
945 subrtx_var_iterator::array_type array;
946 FOR_EACH_SUBRTX_VAR (iter, array, x, NONCONST)
948 rtx x = *iter;
949 if (CONSTANT_P (x))
950 iter.skip_subrtxes ();
951 else
952 switch (GET_CODE (x))
954 case REG:
955 if (cselib_lookup (x, GET_MODE (SUBREG_REG (subreg)), 0, VOIDmode))
956 return false;
957 if (!validate_subreg (GET_MODE (subreg), GET_MODE (x), x,
958 subreg_lowpart_offset (GET_MODE (subreg),
959 GET_MODE (x))))
960 return false;
961 break;
962 case PLUS:
963 case MINUS:
964 case MULT:
965 break;
966 case ASHIFT:
967 iter.substitute (XEXP (x, 0));
968 break;
969 default:
970 return false;
973 return true;
976 /* Transform X into narrower mode MODE from wider mode WMODE. */
978 static rtx
979 use_narrower_mode (rtx x, scalar_int_mode mode, scalar_int_mode wmode)
981 rtx op0, op1;
982 if (CONSTANT_P (x))
983 return lowpart_subreg (mode, x, wmode);
984 switch (GET_CODE (x))
986 case REG:
987 return lowpart_subreg (mode, x, wmode);
988 case PLUS:
989 case MINUS:
990 case MULT:
991 op0 = use_narrower_mode (XEXP (x, 0), mode, wmode);
992 op1 = use_narrower_mode (XEXP (x, 1), mode, wmode);
993 return simplify_gen_binary (GET_CODE (x), mode, op0, op1);
994 case ASHIFT:
995 op0 = use_narrower_mode (XEXP (x, 0), mode, wmode);
996 op1 = XEXP (x, 1);
997 /* Ensure shift amount is not wider than mode. */
998 if (GET_MODE (op1) == VOIDmode)
999 op1 = lowpart_subreg (mode, op1, wmode);
1000 else if (GET_MODE_PRECISION (mode)
1001 < GET_MODE_PRECISION (as_a <scalar_int_mode> (GET_MODE (op1))))
1002 op1 = lowpart_subreg (mode, op1, GET_MODE (op1));
1003 return simplify_gen_binary (ASHIFT, mode, op0, op1);
1004 default:
1005 gcc_unreachable ();
1009 /* Helper function for adjusting used MEMs. */
1011 static rtx
1012 adjust_mems (rtx loc, const_rtx old_rtx, void *data)
1014 struct adjust_mem_data *amd = (struct adjust_mem_data *) data;
1015 rtx mem, addr = loc, tem;
1016 machine_mode mem_mode_save;
1017 bool store_save;
1018 scalar_int_mode tem_mode, tem_subreg_mode;
1019 poly_int64 size;
1020 switch (GET_CODE (loc))
1022 case REG:
1023 /* Don't do any sp or fp replacements outside of MEM addresses
1024 on the LHS. */
1025 if (amd->mem_mode == VOIDmode && amd->store)
1026 return loc;
1027 if (loc == stack_pointer_rtx
1028 && !frame_pointer_needed
1029 && cfa_base_rtx)
1030 return compute_cfa_pointer (amd->stack_adjust);
1031 else if (loc == hard_frame_pointer_rtx
1032 && frame_pointer_needed
1033 && maybe_ne (hard_frame_pointer_adjustment, -1)
1034 && cfa_base_rtx)
1035 return compute_cfa_pointer (hard_frame_pointer_adjustment);
1036 gcc_checking_assert (loc != virtual_incoming_args_rtx);
1037 return loc;
1038 case MEM:
1039 mem = loc;
1040 if (!amd->store)
1042 mem = targetm.delegitimize_address (mem);
1043 if (mem != loc && !MEM_P (mem))
1044 return simplify_replace_fn_rtx (mem, old_rtx, adjust_mems, data);
1047 addr = XEXP (mem, 0);
1048 mem_mode_save = amd->mem_mode;
1049 amd->mem_mode = GET_MODE (mem);
1050 store_save = amd->store;
1051 amd->store = false;
1052 addr = simplify_replace_fn_rtx (addr, old_rtx, adjust_mems, data);
1053 amd->store = store_save;
1054 amd->mem_mode = mem_mode_save;
1055 if (mem == loc)
1056 addr = targetm.delegitimize_address (addr);
1057 if (addr != XEXP (mem, 0))
1058 mem = replace_equiv_address_nv (mem, addr);
1059 if (!amd->store)
1060 mem = avoid_constant_pool_reference (mem);
1061 return mem;
1062 case PRE_INC:
1063 case PRE_DEC:
1064 size = GET_MODE_SIZE (amd->mem_mode);
1065 addr = plus_constant (GET_MODE (loc), XEXP (loc, 0),
1066 GET_CODE (loc) == PRE_INC ? size : -size);
1067 /* FALLTHRU */
1068 case POST_INC:
1069 case POST_DEC:
1070 if (addr == loc)
1071 addr = XEXP (loc, 0);
1072 gcc_assert (amd->mem_mode != VOIDmode && amd->mem_mode != BLKmode);
1073 addr = simplify_replace_fn_rtx (addr, old_rtx, adjust_mems, data);
1074 size = GET_MODE_SIZE (amd->mem_mode);
1075 tem = plus_constant (GET_MODE (loc), XEXP (loc, 0),
1076 (GET_CODE (loc) == PRE_INC
1077 || GET_CODE (loc) == POST_INC) ? size : -size);
1078 store_save = amd->store;
1079 amd->store = false;
1080 tem = simplify_replace_fn_rtx (tem, old_rtx, adjust_mems, data);
1081 amd->store = store_save;
1082 amd->side_effects.safe_push (gen_rtx_SET (XEXP (loc, 0), tem));
1083 return addr;
1084 case PRE_MODIFY:
1085 addr = XEXP (loc, 1);
1086 /* FALLTHRU */
1087 case POST_MODIFY:
1088 if (addr == loc)
1089 addr = XEXP (loc, 0);
1090 gcc_assert (amd->mem_mode != VOIDmode);
1091 addr = simplify_replace_fn_rtx (addr, old_rtx, adjust_mems, data);
1092 store_save = amd->store;
1093 amd->store = false;
1094 tem = simplify_replace_fn_rtx (XEXP (loc, 1), old_rtx,
1095 adjust_mems, data);
1096 amd->store = store_save;
1097 amd->side_effects.safe_push (gen_rtx_SET (XEXP (loc, 0), tem));
1098 return addr;
1099 case SUBREG:
1100 /* First try without delegitimization of whole MEMs and
1101 avoid_constant_pool_reference, which is more likely to succeed. */
1102 store_save = amd->store;
1103 amd->store = true;
1104 addr = simplify_replace_fn_rtx (SUBREG_REG (loc), old_rtx, adjust_mems,
1105 data);
1106 amd->store = store_save;
1107 mem = simplify_replace_fn_rtx (addr, old_rtx, adjust_mems, data);
1108 if (mem == SUBREG_REG (loc))
1110 tem = loc;
1111 goto finish_subreg;
1113 tem = simplify_gen_subreg (GET_MODE (loc), mem,
1114 GET_MODE (SUBREG_REG (loc)),
1115 SUBREG_BYTE (loc));
1116 if (tem)
1117 goto finish_subreg;
1118 tem = simplify_gen_subreg (GET_MODE (loc), addr,
1119 GET_MODE (SUBREG_REG (loc)),
1120 SUBREG_BYTE (loc));
1121 if (tem == NULL_RTX)
1122 tem = gen_rtx_raw_SUBREG (GET_MODE (loc), addr, SUBREG_BYTE (loc));
1123 finish_subreg:
1124 if (MAY_HAVE_DEBUG_BIND_INSNS
1125 && GET_CODE (tem) == SUBREG
1126 && (GET_CODE (SUBREG_REG (tem)) == PLUS
1127 || GET_CODE (SUBREG_REG (tem)) == MINUS
1128 || GET_CODE (SUBREG_REG (tem)) == MULT
1129 || GET_CODE (SUBREG_REG (tem)) == ASHIFT)
1130 && is_a <scalar_int_mode> (GET_MODE (tem), &tem_mode)
1131 && is_a <scalar_int_mode> (GET_MODE (SUBREG_REG (tem)),
1132 &tem_subreg_mode)
1133 && (GET_MODE_PRECISION (tem_mode)
1134 < GET_MODE_PRECISION (tem_subreg_mode))
1135 && subreg_lowpart_p (tem)
1136 && use_narrower_mode_test (SUBREG_REG (tem), tem))
1137 return use_narrower_mode (SUBREG_REG (tem), tem_mode, tem_subreg_mode);
1138 return tem;
1139 case ASM_OPERANDS:
1140 /* Don't do any replacements in second and following
1141 ASM_OPERANDS of inline-asm with multiple sets.
1142 ASM_OPERANDS_INPUT_VEC, ASM_OPERANDS_INPUT_CONSTRAINT_VEC
1143 and ASM_OPERANDS_LABEL_VEC need to be equal between
1144 all the ASM_OPERANDs in the insn and adjust_insn will
1145 fix this up. */
1146 if (ASM_OPERANDS_OUTPUT_IDX (loc) != 0)
1147 return loc;
1148 break;
1149 default:
1150 break;
1152 return NULL_RTX;
1155 /* Helper function for replacement of uses. */
1157 static void
1158 adjust_mem_uses (rtx *x, void *data)
1160 rtx new_x = simplify_replace_fn_rtx (*x, NULL_RTX, adjust_mems, data);
1161 if (new_x != *x)
1162 validate_change (NULL_RTX, x, new_x, true);
1165 /* Helper function for replacement of stores. */
1167 static void
1168 adjust_mem_stores (rtx loc, const_rtx expr, void *data)
1170 if (MEM_P (loc))
1172 rtx new_dest = simplify_replace_fn_rtx (SET_DEST (expr), NULL_RTX,
1173 adjust_mems, data);
1174 if (new_dest != SET_DEST (expr))
1176 rtx xexpr = CONST_CAST_RTX (expr);
1177 validate_change (NULL_RTX, &SET_DEST (xexpr), new_dest, true);
1182 /* Simplify INSN. Remove all {PRE,POST}_{INC,DEC,MODIFY} rtxes,
1183 replace them with their value in the insn and add the side-effects
1184 as other sets to the insn. */
1186 static void
1187 adjust_insn (basic_block bb, rtx_insn *insn)
1189 rtx set;
1191 #ifdef HAVE_window_save
1192 /* If the target machine has an explicit window save instruction, the
1193 transformation OUTGOING_REGNO -> INCOMING_REGNO is done there. */
1194 if (RTX_FRAME_RELATED_P (insn)
1195 && find_reg_note (insn, REG_CFA_WINDOW_SAVE, NULL_RTX))
1197 unsigned int i, nregs = vec_safe_length (windowed_parm_regs);
1198 rtx rtl = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (nregs * 2));
1199 parm_reg *p;
1201 FOR_EACH_VEC_SAFE_ELT (windowed_parm_regs, i, p)
1203 XVECEXP (rtl, 0, i * 2)
1204 = gen_rtx_SET (p->incoming, p->outgoing);
1205 /* Do not clobber the attached DECL, but only the REG. */
1206 XVECEXP (rtl, 0, i * 2 + 1)
1207 = gen_rtx_CLOBBER (GET_MODE (p->outgoing),
1208 gen_raw_REG (GET_MODE (p->outgoing),
1209 REGNO (p->outgoing)));
1212 validate_change (NULL_RTX, &PATTERN (insn), rtl, true);
1213 return;
1215 #endif
1217 adjust_mem_data amd;
1218 amd.mem_mode = VOIDmode;
1219 amd.stack_adjust = -VTI (bb)->out.stack_adjust;
1221 amd.store = true;
1222 note_stores (PATTERN (insn), adjust_mem_stores, &amd);
1224 amd.store = false;
1225 if (GET_CODE (PATTERN (insn)) == PARALLEL
1226 && asm_noperands (PATTERN (insn)) > 0
1227 && GET_CODE (XVECEXP (PATTERN (insn), 0, 0)) == SET)
1229 rtx body, set0;
1230 int i;
1232 /* inline-asm with multiple sets is tiny bit more complicated,
1233 because the 3 vectors in ASM_OPERANDS need to be shared between
1234 all ASM_OPERANDS in the instruction. adjust_mems will
1235 not touch ASM_OPERANDS other than the first one, asm_noperands
1236 test above needs to be called before that (otherwise it would fail)
1237 and afterwards this code fixes it up. */
1238 note_uses (&PATTERN (insn), adjust_mem_uses, &amd);
1239 body = PATTERN (insn);
1240 set0 = XVECEXP (body, 0, 0);
1241 gcc_checking_assert (GET_CODE (set0) == SET
1242 && GET_CODE (SET_SRC (set0)) == ASM_OPERANDS
1243 && ASM_OPERANDS_OUTPUT_IDX (SET_SRC (set0)) == 0);
1244 for (i = 1; i < XVECLEN (body, 0); i++)
1245 if (GET_CODE (XVECEXP (body, 0, i)) != SET)
1246 break;
1247 else
1249 set = XVECEXP (body, 0, i);
1250 gcc_checking_assert (GET_CODE (SET_SRC (set)) == ASM_OPERANDS
1251 && ASM_OPERANDS_OUTPUT_IDX (SET_SRC (set))
1252 == i);
1253 if (ASM_OPERANDS_INPUT_VEC (SET_SRC (set))
1254 != ASM_OPERANDS_INPUT_VEC (SET_SRC (set0))
1255 || ASM_OPERANDS_INPUT_CONSTRAINT_VEC (SET_SRC (set))
1256 != ASM_OPERANDS_INPUT_CONSTRAINT_VEC (SET_SRC (set0))
1257 || ASM_OPERANDS_LABEL_VEC (SET_SRC (set))
1258 != ASM_OPERANDS_LABEL_VEC (SET_SRC (set0)))
1260 rtx newsrc = shallow_copy_rtx (SET_SRC (set));
1261 ASM_OPERANDS_INPUT_VEC (newsrc)
1262 = ASM_OPERANDS_INPUT_VEC (SET_SRC (set0));
1263 ASM_OPERANDS_INPUT_CONSTRAINT_VEC (newsrc)
1264 = ASM_OPERANDS_INPUT_CONSTRAINT_VEC (SET_SRC (set0));
1265 ASM_OPERANDS_LABEL_VEC (newsrc)
1266 = ASM_OPERANDS_LABEL_VEC (SET_SRC (set0));
1267 validate_change (NULL_RTX, &SET_SRC (set), newsrc, true);
1271 else
1272 note_uses (&PATTERN (insn), adjust_mem_uses, &amd);
1274 /* For read-only MEMs containing some constant, prefer those
1275 constants. */
1276 set = single_set (insn);
1277 if (set && MEM_P (SET_SRC (set)) && MEM_READONLY_P (SET_SRC (set)))
1279 rtx note = find_reg_equal_equiv_note (insn);
1281 if (note && CONSTANT_P (XEXP (note, 0)))
1282 validate_change (NULL_RTX, &SET_SRC (set), XEXP (note, 0), true);
1285 if (!amd.side_effects.is_empty ())
1287 rtx *pat, new_pat;
1288 int i, oldn;
1290 pat = &PATTERN (insn);
1291 if (GET_CODE (*pat) == COND_EXEC)
1292 pat = &COND_EXEC_CODE (*pat);
1293 if (GET_CODE (*pat) == PARALLEL)
1294 oldn = XVECLEN (*pat, 0);
1295 else
1296 oldn = 1;
1297 unsigned int newn = amd.side_effects.length ();
1298 new_pat = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (oldn + newn));
1299 if (GET_CODE (*pat) == PARALLEL)
1300 for (i = 0; i < oldn; i++)
1301 XVECEXP (new_pat, 0, i) = XVECEXP (*pat, 0, i);
1302 else
1303 XVECEXP (new_pat, 0, 0) = *pat;
1305 rtx effect;
1306 unsigned int j;
1307 FOR_EACH_VEC_ELT_REVERSE (amd.side_effects, j, effect)
1308 XVECEXP (new_pat, 0, j + oldn) = effect;
1309 validate_change (NULL_RTX, pat, new_pat, true);
1313 /* Return the DEBUG_EXPR of a DEBUG_EXPR_DECL or the VALUE in DV. */
1314 static inline rtx
1315 dv_as_rtx (decl_or_value dv)
1317 tree decl;
1319 if (dv_is_value_p (dv))
1320 return dv_as_value (dv);
1322 decl = dv_as_decl (dv);
1324 gcc_checking_assert (TREE_CODE (decl) == DEBUG_EXPR_DECL);
1325 return DECL_RTL_KNOWN_SET (decl);
1328 /* Return nonzero if a decl_or_value must not have more than one
1329 variable part. The returned value discriminates among various
1330 kinds of one-part DVs ccording to enum onepart_enum. */
1331 static inline onepart_enum
1332 dv_onepart_p (decl_or_value dv)
1334 tree decl;
1336 if (!MAY_HAVE_DEBUG_BIND_INSNS)
1337 return NOT_ONEPART;
1339 if (dv_is_value_p (dv))
1340 return ONEPART_VALUE;
1342 decl = dv_as_decl (dv);
1344 if (TREE_CODE (decl) == DEBUG_EXPR_DECL)
1345 return ONEPART_DEXPR;
1347 if (target_for_debug_bind (decl) != NULL_TREE)
1348 return ONEPART_VDECL;
1350 return NOT_ONEPART;
1353 /* Return the variable pool to be used for a dv of type ONEPART. */
1354 static inline pool_allocator &
1355 onepart_pool (onepart_enum onepart)
1357 return onepart ? valvar_pool : var_pool;
1360 /* Allocate a variable_def from the corresponding variable pool. */
1361 static inline variable *
1362 onepart_pool_allocate (onepart_enum onepart)
1364 return (variable*) onepart_pool (onepart).allocate ();
1367 /* Build a decl_or_value out of a decl. */
1368 static inline decl_or_value
1369 dv_from_decl (tree decl)
1371 decl_or_value dv;
1372 dv = decl;
1373 gcc_checking_assert (dv_is_decl_p (dv));
1374 return dv;
1377 /* Build a decl_or_value out of a value. */
1378 static inline decl_or_value
1379 dv_from_value (rtx value)
1381 decl_or_value dv;
1382 dv = value;
1383 gcc_checking_assert (dv_is_value_p (dv));
1384 return dv;
1387 /* Return a value or the decl of a debug_expr as a decl_or_value. */
1388 static inline decl_or_value
1389 dv_from_rtx (rtx x)
1391 decl_or_value dv;
1393 switch (GET_CODE (x))
1395 case DEBUG_EXPR:
1396 dv = dv_from_decl (DEBUG_EXPR_TREE_DECL (x));
1397 gcc_checking_assert (DECL_RTL_KNOWN_SET (DEBUG_EXPR_TREE_DECL (x)) == x);
1398 break;
1400 case VALUE:
1401 dv = dv_from_value (x);
1402 break;
1404 default:
1405 gcc_unreachable ();
1408 return dv;
1411 extern void debug_dv (decl_or_value dv);
1413 DEBUG_FUNCTION void
1414 debug_dv (decl_or_value dv)
1416 if (dv_is_value_p (dv))
1417 debug_rtx (dv_as_value (dv));
1418 else
1419 debug_generic_stmt (dv_as_decl (dv));
1422 static void loc_exp_dep_clear (variable *var);
1424 /* Free the element of VARIABLE_HTAB (its type is struct variable_def). */
1426 static void
1427 variable_htab_free (void *elem)
1429 int i;
1430 variable *var = (variable *) elem;
1431 location_chain *node, *next;
1433 gcc_checking_assert (var->refcount > 0);
1435 var->refcount--;
1436 if (var->refcount > 0)
1437 return;
1439 for (i = 0; i < var->n_var_parts; i++)
1441 for (node = var->var_part[i].loc_chain; node; node = next)
1443 next = node->next;
1444 delete node;
1446 var->var_part[i].loc_chain = NULL;
1448 if (var->onepart && VAR_LOC_1PAUX (var))
1450 loc_exp_dep_clear (var);
1451 if (VAR_LOC_DEP_LST (var))
1452 VAR_LOC_DEP_LST (var)->pprev = NULL;
1453 XDELETE (VAR_LOC_1PAUX (var));
1454 /* These may be reused across functions, so reset
1455 e.g. NO_LOC_P. */
1456 if (var->onepart == ONEPART_DEXPR)
1457 set_dv_changed (var->dv, true);
1459 onepart_pool (var->onepart).remove (var);
1462 /* Initialize the set (array) SET of attrs to empty lists. */
1464 static void
1465 init_attrs_list_set (attrs **set)
1467 int i;
1469 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
1470 set[i] = NULL;
1473 /* Make the list *LISTP empty. */
1475 static void
1476 attrs_list_clear (attrs **listp)
1478 attrs *list, *next;
1480 for (list = *listp; list; list = next)
1482 next = list->next;
1483 delete list;
1485 *listp = NULL;
1488 /* Return true if the pair of DECL and OFFSET is the member of the LIST. */
1490 static attrs *
1491 attrs_list_member (attrs *list, decl_or_value dv, HOST_WIDE_INT offset)
1493 for (; list; list = list->next)
1494 if (dv_as_opaque (list->dv) == dv_as_opaque (dv) && list->offset == offset)
1495 return list;
1496 return NULL;
1499 /* Insert the triplet DECL, OFFSET, LOC to the list *LISTP. */
1501 static void
1502 attrs_list_insert (attrs **listp, decl_or_value dv,
1503 HOST_WIDE_INT offset, rtx loc)
1505 attrs *list = new attrs;
1506 list->loc = loc;
1507 list->dv = dv;
1508 list->offset = offset;
1509 list->next = *listp;
1510 *listp = list;
1513 /* Copy all nodes from SRC and create a list *DSTP of the copies. */
1515 static void
1516 attrs_list_copy (attrs **dstp, attrs *src)
1518 attrs_list_clear (dstp);
1519 for (; src; src = src->next)
1521 attrs *n = new attrs;
1522 n->loc = src->loc;
1523 n->dv = src->dv;
1524 n->offset = src->offset;
1525 n->next = *dstp;
1526 *dstp = n;
1530 /* Add all nodes from SRC which are not in *DSTP to *DSTP. */
1532 static void
1533 attrs_list_union (attrs **dstp, attrs *src)
1535 for (; src; src = src->next)
1537 if (!attrs_list_member (*dstp, src->dv, src->offset))
1538 attrs_list_insert (dstp, src->dv, src->offset, src->loc);
1542 /* Combine nodes that are not onepart nodes from SRC and SRC2 into
1543 *DSTP. */
1545 static void
1546 attrs_list_mpdv_union (attrs **dstp, attrs *src, attrs *src2)
1548 gcc_assert (!*dstp);
1549 for (; src; src = src->next)
1551 if (!dv_onepart_p (src->dv))
1552 attrs_list_insert (dstp, src->dv, src->offset, src->loc);
1554 for (src = src2; src; src = src->next)
1556 if (!dv_onepart_p (src->dv)
1557 && !attrs_list_member (*dstp, src->dv, src->offset))
1558 attrs_list_insert (dstp, src->dv, src->offset, src->loc);
1562 /* Shared hashtable support. */
1564 /* Return true if VARS is shared. */
1566 static inline bool
1567 shared_hash_shared (shared_hash *vars)
1569 return vars->refcount > 1;
1572 /* Return the hash table for VARS. */
1574 static inline variable_table_type *
1575 shared_hash_htab (shared_hash *vars)
1577 return vars->htab;
1580 /* Return true if VAR is shared, or maybe because VARS is shared. */
1582 static inline bool
1583 shared_var_p (variable *var, shared_hash *vars)
1585 /* Don't count an entry in the changed_variables table as a duplicate. */
1586 return ((var->refcount > 1 + (int) var->in_changed_variables)
1587 || shared_hash_shared (vars));
1590 /* Copy variables into a new hash table. */
1592 static shared_hash *
1593 shared_hash_unshare (shared_hash *vars)
1595 shared_hash *new_vars = new shared_hash;
1596 gcc_assert (vars->refcount > 1);
1597 new_vars->refcount = 1;
1598 new_vars->htab = new variable_table_type (vars->htab->elements () + 3);
1599 vars_copy (new_vars->htab, vars->htab);
1600 vars->refcount--;
1601 return new_vars;
1604 /* Increment reference counter on VARS and return it. */
1606 static inline shared_hash *
1607 shared_hash_copy (shared_hash *vars)
1609 vars->refcount++;
1610 return vars;
1613 /* Decrement reference counter and destroy hash table if not shared
1614 anymore. */
1616 static void
1617 shared_hash_destroy (shared_hash *vars)
1619 gcc_checking_assert (vars->refcount > 0);
1620 if (--vars->refcount == 0)
1622 delete vars->htab;
1623 delete vars;
1627 /* Unshare *PVARS if shared and return slot for DV. If INS is
1628 INSERT, insert it if not already present. */
1630 static inline variable **
1631 shared_hash_find_slot_unshare_1 (shared_hash **pvars, decl_or_value dv,
1632 hashval_t dvhash, enum insert_option ins)
1634 if (shared_hash_shared (*pvars))
1635 *pvars = shared_hash_unshare (*pvars);
1636 return shared_hash_htab (*pvars)->find_slot_with_hash (dv, dvhash, ins);
1639 static inline variable **
1640 shared_hash_find_slot_unshare (shared_hash **pvars, decl_or_value dv,
1641 enum insert_option ins)
1643 return shared_hash_find_slot_unshare_1 (pvars, dv, dv_htab_hash (dv), ins);
1646 /* Return slot for DV, if it is already present in the hash table.
1647 If it is not present, insert it only VARS is not shared, otherwise
1648 return NULL. */
1650 static inline variable **
1651 shared_hash_find_slot_1 (shared_hash *vars, decl_or_value dv, hashval_t dvhash)
1653 return shared_hash_htab (vars)->find_slot_with_hash (dv, dvhash,
1654 shared_hash_shared (vars)
1655 ? NO_INSERT : INSERT);
1658 static inline variable **
1659 shared_hash_find_slot (shared_hash *vars, decl_or_value dv)
1661 return shared_hash_find_slot_1 (vars, dv, dv_htab_hash (dv));
1664 /* Return slot for DV only if it is already present in the hash table. */
1666 static inline variable **
1667 shared_hash_find_slot_noinsert_1 (shared_hash *vars, decl_or_value dv,
1668 hashval_t dvhash)
1670 return shared_hash_htab (vars)->find_slot_with_hash (dv, dvhash, NO_INSERT);
1673 static inline variable **
1674 shared_hash_find_slot_noinsert (shared_hash *vars, decl_or_value dv)
1676 return shared_hash_find_slot_noinsert_1 (vars, dv, dv_htab_hash (dv));
1679 /* Return variable for DV or NULL if not already present in the hash
1680 table. */
1682 static inline variable *
1683 shared_hash_find_1 (shared_hash *vars, decl_or_value dv, hashval_t dvhash)
1685 return shared_hash_htab (vars)->find_with_hash (dv, dvhash);
1688 static inline variable *
1689 shared_hash_find (shared_hash *vars, decl_or_value dv)
1691 return shared_hash_find_1 (vars, dv, dv_htab_hash (dv));
1694 /* Return true if TVAL is better than CVAL as a canonival value. We
1695 choose lowest-numbered VALUEs, using the RTX address as a
1696 tie-breaker. The idea is to arrange them into a star topology,
1697 such that all of them are at most one step away from the canonical
1698 value, and the canonical value has backlinks to all of them, in
1699 addition to all the actual locations. We don't enforce this
1700 topology throughout the entire dataflow analysis, though.
1703 static inline bool
1704 canon_value_cmp (rtx tval, rtx cval)
1706 return !cval
1707 || CSELIB_VAL_PTR (tval)->uid < CSELIB_VAL_PTR (cval)->uid;
1710 static bool dst_can_be_shared;
1712 /* Return a copy of a variable VAR and insert it to dataflow set SET. */
1714 static variable **
1715 unshare_variable (dataflow_set *set, variable **slot, variable *var,
1716 enum var_init_status initialized)
1718 variable *new_var;
1719 int i;
1721 new_var = onepart_pool_allocate (var->onepart);
1722 new_var->dv = var->dv;
1723 new_var->refcount = 1;
1724 var->refcount--;
1725 new_var->n_var_parts = var->n_var_parts;
1726 new_var->onepart = var->onepart;
1727 new_var->in_changed_variables = false;
1729 if (! flag_var_tracking_uninit)
1730 initialized = VAR_INIT_STATUS_INITIALIZED;
1732 for (i = 0; i < var->n_var_parts; i++)
1734 location_chain *node;
1735 location_chain **nextp;
1737 if (i == 0 && var->onepart)
1739 /* One-part auxiliary data is only used while emitting
1740 notes, so propagate it to the new variable in the active
1741 dataflow set. If we're not emitting notes, this will be
1742 a no-op. */
1743 gcc_checking_assert (!VAR_LOC_1PAUX (var) || emit_notes);
1744 VAR_LOC_1PAUX (new_var) = VAR_LOC_1PAUX (var);
1745 VAR_LOC_1PAUX (var) = NULL;
1747 else
1748 VAR_PART_OFFSET (new_var, i) = VAR_PART_OFFSET (var, i);
1749 nextp = &new_var->var_part[i].loc_chain;
1750 for (node = var->var_part[i].loc_chain; node; node = node->next)
1752 location_chain *new_lc;
1754 new_lc = new location_chain;
1755 new_lc->next = NULL;
1756 if (node->init > initialized)
1757 new_lc->init = node->init;
1758 else
1759 new_lc->init = initialized;
1760 if (node->set_src && !(MEM_P (node->set_src)))
1761 new_lc->set_src = node->set_src;
1762 else
1763 new_lc->set_src = NULL;
1764 new_lc->loc = node->loc;
1766 *nextp = new_lc;
1767 nextp = &new_lc->next;
1770 new_var->var_part[i].cur_loc = var->var_part[i].cur_loc;
1773 dst_can_be_shared = false;
1774 if (shared_hash_shared (set->vars))
1775 slot = shared_hash_find_slot_unshare (&set->vars, var->dv, NO_INSERT);
1776 else if (set->traversed_vars && set->vars != set->traversed_vars)
1777 slot = shared_hash_find_slot_noinsert (set->vars, var->dv);
1778 *slot = new_var;
1779 if (var->in_changed_variables)
1781 variable **cslot
1782 = changed_variables->find_slot_with_hash (var->dv,
1783 dv_htab_hash (var->dv),
1784 NO_INSERT);
1785 gcc_assert (*cslot == (void *) var);
1786 var->in_changed_variables = false;
1787 variable_htab_free (var);
1788 *cslot = new_var;
1789 new_var->in_changed_variables = true;
1791 return slot;
1794 /* Copy all variables from hash table SRC to hash table DST. */
1796 static void
1797 vars_copy (variable_table_type *dst, variable_table_type *src)
1799 variable_iterator_type hi;
1800 variable *var;
1802 FOR_EACH_HASH_TABLE_ELEMENT (*src, var, variable, hi)
1804 variable **dstp;
1805 var->refcount++;
1806 dstp = dst->find_slot_with_hash (var->dv, dv_htab_hash (var->dv),
1807 INSERT);
1808 *dstp = var;
1812 /* Map a decl to its main debug decl. */
1814 static inline tree
1815 var_debug_decl (tree decl)
1817 if (decl && VAR_P (decl) && DECL_HAS_DEBUG_EXPR_P (decl))
1819 tree debugdecl = DECL_DEBUG_EXPR (decl);
1820 if (DECL_P (debugdecl))
1821 decl = debugdecl;
1824 return decl;
1827 /* Set the register LOC to contain DV, OFFSET. */
1829 static void
1830 var_reg_decl_set (dataflow_set *set, rtx loc, enum var_init_status initialized,
1831 decl_or_value dv, HOST_WIDE_INT offset, rtx set_src,
1832 enum insert_option iopt)
1834 attrs *node;
1835 bool decl_p = dv_is_decl_p (dv);
1837 if (decl_p)
1838 dv = dv_from_decl (var_debug_decl (dv_as_decl (dv)));
1840 for (node = set->regs[REGNO (loc)]; node; node = node->next)
1841 if (dv_as_opaque (node->dv) == dv_as_opaque (dv)
1842 && node->offset == offset)
1843 break;
1844 if (!node)
1845 attrs_list_insert (&set->regs[REGNO (loc)], dv, offset, loc);
1846 set_variable_part (set, loc, dv, offset, initialized, set_src, iopt);
1849 /* Return true if we should track a location that is OFFSET bytes from
1850 a variable. Store the constant offset in *OFFSET_OUT if so. */
1852 static bool
1853 track_offset_p (poly_int64 offset, HOST_WIDE_INT *offset_out)
1855 HOST_WIDE_INT const_offset;
1856 if (!offset.is_constant (&const_offset)
1857 || !IN_RANGE (const_offset, 0, MAX_VAR_PARTS - 1))
1858 return false;
1859 *offset_out = const_offset;
1860 return true;
1863 /* Return the offset of a register that track_offset_p says we
1864 should track. */
1866 static HOST_WIDE_INT
1867 get_tracked_reg_offset (rtx loc)
1869 HOST_WIDE_INT offset;
1870 if (!track_offset_p (REG_OFFSET (loc), &offset))
1871 gcc_unreachable ();
1872 return offset;
1875 /* Set the register to contain REG_EXPR (LOC), REG_OFFSET (LOC). */
1877 static void
1878 var_reg_set (dataflow_set *set, rtx loc, enum var_init_status initialized,
1879 rtx set_src)
1881 tree decl = REG_EXPR (loc);
1882 HOST_WIDE_INT offset = get_tracked_reg_offset (loc);
1884 var_reg_decl_set (set, loc, initialized,
1885 dv_from_decl (decl), offset, set_src, INSERT);
1888 static enum var_init_status
1889 get_init_value (dataflow_set *set, rtx loc, decl_or_value dv)
1891 variable *var;
1892 int i;
1893 enum var_init_status ret_val = VAR_INIT_STATUS_UNKNOWN;
1895 if (! flag_var_tracking_uninit)
1896 return VAR_INIT_STATUS_INITIALIZED;
1898 var = shared_hash_find (set->vars, dv);
1899 if (var)
1901 for (i = 0; i < var->n_var_parts && ret_val == VAR_INIT_STATUS_UNKNOWN; i++)
1903 location_chain *nextp;
1904 for (nextp = var->var_part[i].loc_chain; nextp; nextp = nextp->next)
1905 if (rtx_equal_p (nextp->loc, loc))
1907 ret_val = nextp->init;
1908 break;
1913 return ret_val;
1916 /* Delete current content of register LOC in dataflow set SET and set
1917 the register to contain REG_EXPR (LOC), REG_OFFSET (LOC). If
1918 MODIFY is true, any other live copies of the same variable part are
1919 also deleted from the dataflow set, otherwise the variable part is
1920 assumed to be copied from another location holding the same
1921 part. */
1923 static void
1924 var_reg_delete_and_set (dataflow_set *set, rtx loc, bool modify,
1925 enum var_init_status initialized, rtx set_src)
1927 tree decl = REG_EXPR (loc);
1928 HOST_WIDE_INT offset = get_tracked_reg_offset (loc);
1929 attrs *node, *next;
1930 attrs **nextp;
1932 decl = var_debug_decl (decl);
1934 if (initialized == VAR_INIT_STATUS_UNKNOWN)
1935 initialized = get_init_value (set, loc, dv_from_decl (decl));
1937 nextp = &set->regs[REGNO (loc)];
1938 for (node = *nextp; node; node = next)
1940 next = node->next;
1941 if (dv_as_opaque (node->dv) != decl || node->offset != offset)
1943 delete_variable_part (set, node->loc, node->dv, node->offset);
1944 delete node;
1945 *nextp = next;
1947 else
1949 node->loc = loc;
1950 nextp = &node->next;
1953 if (modify)
1954 clobber_variable_part (set, loc, dv_from_decl (decl), offset, set_src);
1955 var_reg_set (set, loc, initialized, set_src);
1958 /* Delete the association of register LOC in dataflow set SET with any
1959 variables that aren't onepart. If CLOBBER is true, also delete any
1960 other live copies of the same variable part, and delete the
1961 association with onepart dvs too. */
1963 static void
1964 var_reg_delete (dataflow_set *set, rtx loc, bool clobber)
1966 attrs **nextp = &set->regs[REGNO (loc)];
1967 attrs *node, *next;
1969 HOST_WIDE_INT offset;
1970 if (clobber && track_offset_p (REG_OFFSET (loc), &offset))
1972 tree decl = REG_EXPR (loc);
1974 decl = var_debug_decl (decl);
1976 clobber_variable_part (set, NULL, dv_from_decl (decl), offset, NULL);
1979 for (node = *nextp; node; node = next)
1981 next = node->next;
1982 if (clobber || !dv_onepart_p (node->dv))
1984 delete_variable_part (set, node->loc, node->dv, node->offset);
1985 delete node;
1986 *nextp = next;
1988 else
1989 nextp = &node->next;
1993 /* Delete content of register with number REGNO in dataflow set SET. */
1995 static void
1996 var_regno_delete (dataflow_set *set, int regno)
1998 attrs **reg = &set->regs[regno];
1999 attrs *node, *next;
2001 for (node = *reg; node; node = next)
2003 next = node->next;
2004 delete_variable_part (set, node->loc, node->dv, node->offset);
2005 delete node;
2007 *reg = NULL;
2010 /* Return true if I is the negated value of a power of two. */
2011 static bool
2012 negative_power_of_two_p (HOST_WIDE_INT i)
2014 unsigned HOST_WIDE_INT x = -(unsigned HOST_WIDE_INT)i;
2015 return pow2_or_zerop (x);
2018 /* Strip constant offsets and alignments off of LOC. Return the base
2019 expression. */
2021 static rtx
2022 vt_get_canonicalize_base (rtx loc)
2024 while ((GET_CODE (loc) == PLUS
2025 || GET_CODE (loc) == AND)
2026 && GET_CODE (XEXP (loc, 1)) == CONST_INT
2027 && (GET_CODE (loc) != AND
2028 || negative_power_of_two_p (INTVAL (XEXP (loc, 1)))))
2029 loc = XEXP (loc, 0);
2031 return loc;
2034 /* This caches canonicalized addresses for VALUEs, computed using
2035 information in the global cselib table. */
2036 static hash_map<rtx, rtx> *global_get_addr_cache;
2038 /* This caches canonicalized addresses for VALUEs, computed using
2039 information from the global cache and information pertaining to a
2040 basic block being analyzed. */
2041 static hash_map<rtx, rtx> *local_get_addr_cache;
2043 static rtx vt_canonicalize_addr (dataflow_set *, rtx);
2045 /* Return the canonical address for LOC, that must be a VALUE, using a
2046 cached global equivalence or computing it and storing it in the
2047 global cache. */
2049 static rtx
2050 get_addr_from_global_cache (rtx const loc)
2052 rtx x;
2054 gcc_checking_assert (GET_CODE (loc) == VALUE);
2056 bool existed;
2057 rtx *slot = &global_get_addr_cache->get_or_insert (loc, &existed);
2058 if (existed)
2059 return *slot;
2061 x = canon_rtx (get_addr (loc));
2063 /* Tentative, avoiding infinite recursion. */
2064 *slot = x;
2066 if (x != loc)
2068 rtx nx = vt_canonicalize_addr (NULL, x);
2069 if (nx != x)
2071 /* The table may have moved during recursion, recompute
2072 SLOT. */
2073 *global_get_addr_cache->get (loc) = x = nx;
2077 return x;
2080 /* Return the canonical address for LOC, that must be a VALUE, using a
2081 cached local equivalence or computing it and storing it in the
2082 local cache. */
2084 static rtx
2085 get_addr_from_local_cache (dataflow_set *set, rtx const loc)
2087 rtx x;
2088 decl_or_value dv;
2089 variable *var;
2090 location_chain *l;
2092 gcc_checking_assert (GET_CODE (loc) == VALUE);
2094 bool existed;
2095 rtx *slot = &local_get_addr_cache->get_or_insert (loc, &existed);
2096 if (existed)
2097 return *slot;
2099 x = get_addr_from_global_cache (loc);
2101 /* Tentative, avoiding infinite recursion. */
2102 *slot = x;
2104 /* Recurse to cache local expansion of X, or if we need to search
2105 for a VALUE in the expansion. */
2106 if (x != loc)
2108 rtx nx = vt_canonicalize_addr (set, x);
2109 if (nx != x)
2111 slot = local_get_addr_cache->get (loc);
2112 *slot = x = nx;
2114 return x;
2117 dv = dv_from_rtx (x);
2118 var = shared_hash_find (set->vars, dv);
2119 if (!var)
2120 return x;
2122 /* Look for an improved equivalent expression. */
2123 for (l = var->var_part[0].loc_chain; l; l = l->next)
2125 rtx base = vt_get_canonicalize_base (l->loc);
2126 if (GET_CODE (base) == VALUE
2127 && canon_value_cmp (base, loc))
2129 rtx nx = vt_canonicalize_addr (set, l->loc);
2130 if (x != nx)
2132 slot = local_get_addr_cache->get (loc);
2133 *slot = x = nx;
2135 break;
2139 return x;
2142 /* Canonicalize LOC using equivalences from SET in addition to those
2143 in the cselib static table. It expects a VALUE-based expression,
2144 and it will only substitute VALUEs with other VALUEs or
2145 function-global equivalences, so that, if two addresses have base
2146 VALUEs that are locally or globally related in ways that
2147 memrefs_conflict_p cares about, they will both canonicalize to
2148 expressions that have the same base VALUE.
2150 The use of VALUEs as canonical base addresses enables the canonical
2151 RTXs to remain unchanged globally, if they resolve to a constant,
2152 or throughout a basic block otherwise, so that they can be cached
2153 and the cache needs not be invalidated when REGs, MEMs or such
2154 change. */
2156 static rtx
2157 vt_canonicalize_addr (dataflow_set *set, rtx oloc)
2159 poly_int64 ofst = 0, term;
2160 machine_mode mode = GET_MODE (oloc);
2161 rtx loc = oloc;
2162 rtx x;
2163 bool retry = true;
2165 while (retry)
2167 while (GET_CODE (loc) == PLUS
2168 && poly_int_rtx_p (XEXP (loc, 1), &term))
2170 ofst += term;
2171 loc = XEXP (loc, 0);
2174 /* Alignment operations can't normally be combined, so just
2175 canonicalize the base and we're done. We'll normally have
2176 only one stack alignment anyway. */
2177 if (GET_CODE (loc) == AND
2178 && GET_CODE (XEXP (loc, 1)) == CONST_INT
2179 && negative_power_of_two_p (INTVAL (XEXP (loc, 1))))
2181 x = vt_canonicalize_addr (set, XEXP (loc, 0));
2182 if (x != XEXP (loc, 0))
2183 loc = gen_rtx_AND (mode, x, XEXP (loc, 1));
2184 retry = false;
2187 if (GET_CODE (loc) == VALUE)
2189 if (set)
2190 loc = get_addr_from_local_cache (set, loc);
2191 else
2192 loc = get_addr_from_global_cache (loc);
2194 /* Consolidate plus_constants. */
2195 while (maybe_ne (ofst, 0)
2196 && GET_CODE (loc) == PLUS
2197 && poly_int_rtx_p (XEXP (loc, 1), &term))
2199 ofst += term;
2200 loc = XEXP (loc, 0);
2203 retry = false;
2205 else
2207 x = canon_rtx (loc);
2208 if (retry)
2209 retry = (x != loc);
2210 loc = x;
2214 /* Add OFST back in. */
2215 if (maybe_ne (ofst, 0))
2217 /* Don't build new RTL if we can help it. */
2218 if (strip_offset (oloc, &term) == loc && known_eq (term, ofst))
2219 return oloc;
2221 loc = plus_constant (mode, loc, ofst);
2224 return loc;
2227 /* Return true iff there's a true dependence between MLOC and LOC.
2228 MADDR must be a canonicalized version of MLOC's address. */
2230 static inline bool
2231 vt_canon_true_dep (dataflow_set *set, rtx mloc, rtx maddr, rtx loc)
2233 if (GET_CODE (loc) != MEM)
2234 return false;
2236 rtx addr = vt_canonicalize_addr (set, XEXP (loc, 0));
2237 if (!canon_true_dependence (mloc, GET_MODE (mloc), maddr, loc, addr))
2238 return false;
2240 return true;
2243 /* Hold parameters for the hashtab traversal function
2244 drop_overlapping_mem_locs, see below. */
2246 struct overlapping_mems
2248 dataflow_set *set;
2249 rtx loc, addr;
2252 /* Remove all MEMs that overlap with COMS->LOC from the location list
2253 of a hash table entry for a onepart variable. COMS->ADDR must be a
2254 canonicalized form of COMS->LOC's address, and COMS->LOC must be
2255 canonicalized itself. */
2258 drop_overlapping_mem_locs (variable **slot, overlapping_mems *coms)
2260 dataflow_set *set = coms->set;
2261 rtx mloc = coms->loc, addr = coms->addr;
2262 variable *var = *slot;
2264 if (var->onepart != NOT_ONEPART)
2266 location_chain *loc, **locp;
2267 bool changed = false;
2268 rtx cur_loc;
2270 gcc_assert (var->n_var_parts == 1);
2272 if (shared_var_p (var, set->vars))
2274 for (loc = var->var_part[0].loc_chain; loc; loc = loc->next)
2275 if (vt_canon_true_dep (set, mloc, addr, loc->loc))
2276 break;
2278 if (!loc)
2279 return 1;
2281 slot = unshare_variable (set, slot, var, VAR_INIT_STATUS_UNKNOWN);
2282 var = *slot;
2283 gcc_assert (var->n_var_parts == 1);
2286 if (VAR_LOC_1PAUX (var))
2287 cur_loc = VAR_LOC_FROM (var);
2288 else
2289 cur_loc = var->var_part[0].cur_loc;
2291 for (locp = &var->var_part[0].loc_chain, loc = *locp;
2292 loc; loc = *locp)
2294 if (!vt_canon_true_dep (set, mloc, addr, loc->loc))
2296 locp = &loc->next;
2297 continue;
2300 *locp = loc->next;
2301 /* If we have deleted the location which was last emitted
2302 we have to emit new location so add the variable to set
2303 of changed variables. */
2304 if (cur_loc == loc->loc)
2306 changed = true;
2307 var->var_part[0].cur_loc = NULL;
2308 if (VAR_LOC_1PAUX (var))
2309 VAR_LOC_FROM (var) = NULL;
2311 delete loc;
2314 if (!var->var_part[0].loc_chain)
2316 var->n_var_parts--;
2317 changed = true;
2319 if (changed)
2320 variable_was_changed (var, set);
2323 return 1;
2326 /* Remove from SET all VALUE bindings to MEMs that overlap with LOC. */
2328 static void
2329 clobber_overlapping_mems (dataflow_set *set, rtx loc)
2331 struct overlapping_mems coms;
2333 gcc_checking_assert (GET_CODE (loc) == MEM);
2335 coms.set = set;
2336 coms.loc = canon_rtx (loc);
2337 coms.addr = vt_canonicalize_addr (set, XEXP (loc, 0));
2339 set->traversed_vars = set->vars;
2340 shared_hash_htab (set->vars)
2341 ->traverse <overlapping_mems*, drop_overlapping_mem_locs> (&coms);
2342 set->traversed_vars = NULL;
2345 /* Set the location of DV, OFFSET as the MEM LOC. */
2347 static void
2348 var_mem_decl_set (dataflow_set *set, rtx loc, enum var_init_status initialized,
2349 decl_or_value dv, HOST_WIDE_INT offset, rtx set_src,
2350 enum insert_option iopt)
2352 if (dv_is_decl_p (dv))
2353 dv = dv_from_decl (var_debug_decl (dv_as_decl (dv)));
2355 set_variable_part (set, loc, dv, offset, initialized, set_src, iopt);
2358 /* Set the location part of variable MEM_EXPR (LOC) in dataflow set
2359 SET to LOC.
2360 Adjust the address first if it is stack pointer based. */
2362 static void
2363 var_mem_set (dataflow_set *set, rtx loc, enum var_init_status initialized,
2364 rtx set_src)
2366 tree decl = MEM_EXPR (loc);
2367 HOST_WIDE_INT offset = int_mem_offset (loc);
2369 var_mem_decl_set (set, loc, initialized,
2370 dv_from_decl (decl), offset, set_src, INSERT);
2373 /* Delete and set the location part of variable MEM_EXPR (LOC) in
2374 dataflow set SET to LOC. If MODIFY is true, any other live copies
2375 of the same variable part are also deleted from the dataflow set,
2376 otherwise the variable part is assumed to be copied from another
2377 location holding the same part.
2378 Adjust the address first if it is stack pointer based. */
2380 static void
2381 var_mem_delete_and_set (dataflow_set *set, rtx loc, bool modify,
2382 enum var_init_status initialized, rtx set_src)
2384 tree decl = MEM_EXPR (loc);
2385 HOST_WIDE_INT offset = int_mem_offset (loc);
2387 clobber_overlapping_mems (set, loc);
2388 decl = var_debug_decl (decl);
2390 if (initialized == VAR_INIT_STATUS_UNKNOWN)
2391 initialized = get_init_value (set, loc, dv_from_decl (decl));
2393 if (modify)
2394 clobber_variable_part (set, NULL, dv_from_decl (decl), offset, set_src);
2395 var_mem_set (set, loc, initialized, set_src);
2398 /* Delete the location part LOC from dataflow set SET. If CLOBBER is
2399 true, also delete any other live copies of the same variable part.
2400 Adjust the address first if it is stack pointer based. */
2402 static void
2403 var_mem_delete (dataflow_set *set, rtx loc, bool clobber)
2405 tree decl = MEM_EXPR (loc);
2406 HOST_WIDE_INT offset = int_mem_offset (loc);
2408 clobber_overlapping_mems (set, loc);
2409 decl = var_debug_decl (decl);
2410 if (clobber)
2411 clobber_variable_part (set, NULL, dv_from_decl (decl), offset, NULL);
2412 delete_variable_part (set, loc, dv_from_decl (decl), offset);
2415 /* Return true if LOC should not be expanded for location expressions,
2416 or used in them. */
2418 static inline bool
2419 unsuitable_loc (rtx loc)
2421 switch (GET_CODE (loc))
2423 case PC:
2424 case SCRATCH:
2425 case CC0:
2426 case ASM_INPUT:
2427 case ASM_OPERANDS:
2428 return true;
2430 default:
2431 return false;
2435 /* Bind VAL to LOC in SET. If MODIFIED, detach LOC from any values
2436 bound to it. */
2438 static inline void
2439 val_bind (dataflow_set *set, rtx val, rtx loc, bool modified)
2441 if (REG_P (loc))
2443 if (modified)
2444 var_regno_delete (set, REGNO (loc));
2445 var_reg_decl_set (set, loc, VAR_INIT_STATUS_INITIALIZED,
2446 dv_from_value (val), 0, NULL_RTX, INSERT);
2448 else if (MEM_P (loc))
2450 struct elt_loc_list *l = CSELIB_VAL_PTR (val)->locs;
2452 if (modified)
2453 clobber_overlapping_mems (set, loc);
2455 if (l && GET_CODE (l->loc) == VALUE)
2456 l = canonical_cselib_val (CSELIB_VAL_PTR (l->loc))->locs;
2458 /* If this MEM is a global constant, we don't need it in the
2459 dynamic tables. ??? We should test this before emitting the
2460 micro-op in the first place. */
2461 while (l)
2462 if (GET_CODE (l->loc) == MEM && XEXP (l->loc, 0) == XEXP (loc, 0))
2463 break;
2464 else
2465 l = l->next;
2467 if (!l)
2468 var_mem_decl_set (set, loc, VAR_INIT_STATUS_INITIALIZED,
2469 dv_from_value (val), 0, NULL_RTX, INSERT);
2471 else
2473 /* Other kinds of equivalences are necessarily static, at least
2474 so long as we do not perform substitutions while merging
2475 expressions. */
2476 gcc_unreachable ();
2477 set_variable_part (set, loc, dv_from_value (val), 0,
2478 VAR_INIT_STATUS_INITIALIZED, NULL_RTX, INSERT);
2482 /* Bind a value to a location it was just stored in. If MODIFIED
2483 holds, assume the location was modified, detaching it from any
2484 values bound to it. */
2486 static void
2487 val_store (dataflow_set *set, rtx val, rtx loc, rtx_insn *insn,
2488 bool modified)
2490 cselib_val *v = CSELIB_VAL_PTR (val);
2492 gcc_assert (cselib_preserved_value_p (v));
2494 if (dump_file)
2496 fprintf (dump_file, "%i: ", insn ? INSN_UID (insn) : 0);
2497 print_inline_rtx (dump_file, loc, 0);
2498 fprintf (dump_file, " evaluates to ");
2499 print_inline_rtx (dump_file, val, 0);
2500 if (v->locs)
2502 struct elt_loc_list *l;
2503 for (l = v->locs; l; l = l->next)
2505 fprintf (dump_file, "\n%i: ", INSN_UID (l->setting_insn));
2506 print_inline_rtx (dump_file, l->loc, 0);
2509 fprintf (dump_file, "\n");
2512 gcc_checking_assert (!unsuitable_loc (loc));
2514 val_bind (set, val, loc, modified);
2517 /* Clear (canonical address) slots that reference X. */
2519 bool
2520 local_get_addr_clear_given_value (rtx const &, rtx *slot, rtx x)
2522 if (vt_get_canonicalize_base (*slot) == x)
2523 *slot = NULL;
2524 return true;
2527 /* Reset this node, detaching all its equivalences. Return the slot
2528 in the variable hash table that holds dv, if there is one. */
2530 static void
2531 val_reset (dataflow_set *set, decl_or_value dv)
2533 variable *var = shared_hash_find (set->vars, dv) ;
2534 location_chain *node;
2535 rtx cval;
2537 if (!var || !var->n_var_parts)
2538 return;
2540 gcc_assert (var->n_var_parts == 1);
2542 if (var->onepart == ONEPART_VALUE)
2544 rtx x = dv_as_value (dv);
2546 /* Relationships in the global cache don't change, so reset the
2547 local cache entry only. */
2548 rtx *slot = local_get_addr_cache->get (x);
2549 if (slot)
2551 /* If the value resolved back to itself, odds are that other
2552 values may have cached it too. These entries now refer
2553 to the old X, so detach them too. Entries that used the
2554 old X but resolved to something else remain ok as long as
2555 that something else isn't also reset. */
2556 if (*slot == x)
2557 local_get_addr_cache
2558 ->traverse<rtx, local_get_addr_clear_given_value> (x);
2559 *slot = NULL;
2563 cval = NULL;
2564 for (node = var->var_part[0].loc_chain; node; node = node->next)
2565 if (GET_CODE (node->loc) == VALUE
2566 && canon_value_cmp (node->loc, cval))
2567 cval = node->loc;
2569 for (node = var->var_part[0].loc_chain; node; node = node->next)
2570 if (GET_CODE (node->loc) == VALUE && cval != node->loc)
2572 /* Redirect the equivalence link to the new canonical
2573 value, or simply remove it if it would point at
2574 itself. */
2575 if (cval)
2576 set_variable_part (set, cval, dv_from_value (node->loc),
2577 0, node->init, node->set_src, NO_INSERT);
2578 delete_variable_part (set, dv_as_value (dv),
2579 dv_from_value (node->loc), 0);
2582 if (cval)
2584 decl_or_value cdv = dv_from_value (cval);
2586 /* Keep the remaining values connected, accumulating links
2587 in the canonical value. */
2588 for (node = var->var_part[0].loc_chain; node; node = node->next)
2590 if (node->loc == cval)
2591 continue;
2592 else if (GET_CODE (node->loc) == REG)
2593 var_reg_decl_set (set, node->loc, node->init, cdv, 0,
2594 node->set_src, NO_INSERT);
2595 else if (GET_CODE (node->loc) == MEM)
2596 var_mem_decl_set (set, node->loc, node->init, cdv, 0,
2597 node->set_src, NO_INSERT);
2598 else
2599 set_variable_part (set, node->loc, cdv, 0,
2600 node->init, node->set_src, NO_INSERT);
2604 /* We remove this last, to make sure that the canonical value is not
2605 removed to the point of requiring reinsertion. */
2606 if (cval)
2607 delete_variable_part (set, dv_as_value (dv), dv_from_value (cval), 0);
2609 clobber_variable_part (set, NULL, dv, 0, NULL);
2612 /* Find the values in a given location and map the val to another
2613 value, if it is unique, or add the location as one holding the
2614 value. */
2616 static void
2617 val_resolve (dataflow_set *set, rtx val, rtx loc, rtx_insn *insn)
2619 decl_or_value dv = dv_from_value (val);
2621 if (dump_file && (dump_flags & TDF_DETAILS))
2623 if (insn)
2624 fprintf (dump_file, "%i: ", INSN_UID (insn));
2625 else
2626 fprintf (dump_file, "head: ");
2627 print_inline_rtx (dump_file, val, 0);
2628 fputs (" is at ", dump_file);
2629 print_inline_rtx (dump_file, loc, 0);
2630 fputc ('\n', dump_file);
2633 val_reset (set, dv);
2635 gcc_checking_assert (!unsuitable_loc (loc));
2637 if (REG_P (loc))
2639 attrs *node, *found = NULL;
2641 for (node = set->regs[REGNO (loc)]; node; node = node->next)
2642 if (dv_is_value_p (node->dv)
2643 && GET_MODE (dv_as_value (node->dv)) == GET_MODE (loc))
2645 found = node;
2647 /* Map incoming equivalences. ??? Wouldn't it be nice if
2648 we just started sharing the location lists? Maybe a
2649 circular list ending at the value itself or some
2650 such. */
2651 set_variable_part (set, dv_as_value (node->dv),
2652 dv_from_value (val), node->offset,
2653 VAR_INIT_STATUS_INITIALIZED, NULL_RTX, INSERT);
2654 set_variable_part (set, val, node->dv, node->offset,
2655 VAR_INIT_STATUS_INITIALIZED, NULL_RTX, INSERT);
2658 /* If we didn't find any equivalence, we need to remember that
2659 this value is held in the named register. */
2660 if (found)
2661 return;
2663 /* ??? Attempt to find and merge equivalent MEMs or other
2664 expressions too. */
2666 val_bind (set, val, loc, false);
2669 /* Initialize dataflow set SET to be empty.
2670 VARS_SIZE is the initial size of hash table VARS. */
2672 static void
2673 dataflow_set_init (dataflow_set *set)
2675 init_attrs_list_set (set->regs);
2676 set->vars = shared_hash_copy (empty_shared_hash);
2677 set->stack_adjust = 0;
2678 set->traversed_vars = NULL;
2681 /* Delete the contents of dataflow set SET. */
2683 static void
2684 dataflow_set_clear (dataflow_set *set)
2686 int i;
2688 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
2689 attrs_list_clear (&set->regs[i]);
2691 shared_hash_destroy (set->vars);
2692 set->vars = shared_hash_copy (empty_shared_hash);
2695 /* Copy the contents of dataflow set SRC to DST. */
2697 static void
2698 dataflow_set_copy (dataflow_set *dst, dataflow_set *src)
2700 int i;
2702 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
2703 attrs_list_copy (&dst->regs[i], src->regs[i]);
2705 shared_hash_destroy (dst->vars);
2706 dst->vars = shared_hash_copy (src->vars);
2707 dst->stack_adjust = src->stack_adjust;
2710 /* Information for merging lists of locations for a given offset of variable.
2712 struct variable_union_info
2714 /* Node of the location chain. */
2715 location_chain *lc;
2717 /* The sum of positions in the input chains. */
2718 int pos;
2720 /* The position in the chain of DST dataflow set. */
2721 int pos_dst;
2724 /* Buffer for location list sorting and its allocated size. */
2725 static struct variable_union_info *vui_vec;
2726 static int vui_allocated;
2728 /* Compare function for qsort, order the structures by POS element. */
2730 static int
2731 variable_union_info_cmp_pos (const void *n1, const void *n2)
2733 const struct variable_union_info *const i1 =
2734 (const struct variable_union_info *) n1;
2735 const struct variable_union_info *const i2 =
2736 ( const struct variable_union_info *) n2;
2738 if (i1->pos != i2->pos)
2739 return i1->pos - i2->pos;
2741 return (i1->pos_dst - i2->pos_dst);
2744 /* Compute union of location parts of variable *SLOT and the same variable
2745 from hash table DATA. Compute "sorted" union of the location chains
2746 for common offsets, i.e. the locations of a variable part are sorted by
2747 a priority where the priority is the sum of the positions in the 2 chains
2748 (if a location is only in one list the position in the second list is
2749 defined to be larger than the length of the chains).
2750 When we are updating the location parts the newest location is in the
2751 beginning of the chain, so when we do the described "sorted" union
2752 we keep the newest locations in the beginning. */
2754 static int
2755 variable_union (variable *src, dataflow_set *set)
2757 variable *dst;
2758 variable **dstp;
2759 int i, j, k;
2761 dstp = shared_hash_find_slot (set->vars, src->dv);
2762 if (!dstp || !*dstp)
2764 src->refcount++;
2766 dst_can_be_shared = false;
2767 if (!dstp)
2768 dstp = shared_hash_find_slot_unshare (&set->vars, src->dv, INSERT);
2770 *dstp = src;
2772 /* Continue traversing the hash table. */
2773 return 1;
2775 else
2776 dst = *dstp;
2778 gcc_assert (src->n_var_parts);
2779 gcc_checking_assert (src->onepart == dst->onepart);
2781 /* We can combine one-part variables very efficiently, because their
2782 entries are in canonical order. */
2783 if (src->onepart)
2785 location_chain **nodep, *dnode, *snode;
2787 gcc_assert (src->n_var_parts == 1
2788 && dst->n_var_parts == 1);
2790 snode = src->var_part[0].loc_chain;
2791 gcc_assert (snode);
2793 restart_onepart_unshared:
2794 nodep = &dst->var_part[0].loc_chain;
2795 dnode = *nodep;
2796 gcc_assert (dnode);
2798 while (snode)
2800 int r = dnode ? loc_cmp (dnode->loc, snode->loc) : 1;
2802 if (r > 0)
2804 location_chain *nnode;
2806 if (shared_var_p (dst, set->vars))
2808 dstp = unshare_variable (set, dstp, dst,
2809 VAR_INIT_STATUS_INITIALIZED);
2810 dst = *dstp;
2811 goto restart_onepart_unshared;
2814 *nodep = nnode = new location_chain;
2815 nnode->loc = snode->loc;
2816 nnode->init = snode->init;
2817 if (!snode->set_src || MEM_P (snode->set_src))
2818 nnode->set_src = NULL;
2819 else
2820 nnode->set_src = snode->set_src;
2821 nnode->next = dnode;
2822 dnode = nnode;
2824 else if (r == 0)
2825 gcc_checking_assert (rtx_equal_p (dnode->loc, snode->loc));
2827 if (r >= 0)
2828 snode = snode->next;
2830 nodep = &dnode->next;
2831 dnode = *nodep;
2834 return 1;
2837 gcc_checking_assert (!src->onepart);
2839 /* Count the number of location parts, result is K. */
2840 for (i = 0, j = 0, k = 0;
2841 i < src->n_var_parts && j < dst->n_var_parts; k++)
2843 if (VAR_PART_OFFSET (src, i) == VAR_PART_OFFSET (dst, j))
2845 i++;
2846 j++;
2848 else if (VAR_PART_OFFSET (src, i) < VAR_PART_OFFSET (dst, j))
2849 i++;
2850 else
2851 j++;
2853 k += src->n_var_parts - i;
2854 k += dst->n_var_parts - j;
2856 /* We track only variables whose size is <= MAX_VAR_PARTS bytes
2857 thus there are at most MAX_VAR_PARTS different offsets. */
2858 gcc_checking_assert (dst->onepart ? k == 1 : k <= MAX_VAR_PARTS);
2860 if (dst->n_var_parts != k && shared_var_p (dst, set->vars))
2862 dstp = unshare_variable (set, dstp, dst, VAR_INIT_STATUS_UNKNOWN);
2863 dst = *dstp;
2866 i = src->n_var_parts - 1;
2867 j = dst->n_var_parts - 1;
2868 dst->n_var_parts = k;
2870 for (k--; k >= 0; k--)
2872 location_chain *node, *node2;
2874 if (i >= 0 && j >= 0
2875 && VAR_PART_OFFSET (src, i) == VAR_PART_OFFSET (dst, j))
2877 /* Compute the "sorted" union of the chains, i.e. the locations which
2878 are in both chains go first, they are sorted by the sum of
2879 positions in the chains. */
2880 int dst_l, src_l;
2881 int ii, jj, n;
2882 struct variable_union_info *vui;
2884 /* If DST is shared compare the location chains.
2885 If they are different we will modify the chain in DST with
2886 high probability so make a copy of DST. */
2887 if (shared_var_p (dst, set->vars))
2889 for (node = src->var_part[i].loc_chain,
2890 node2 = dst->var_part[j].loc_chain; node && node2;
2891 node = node->next, node2 = node2->next)
2893 if (!((REG_P (node2->loc)
2894 && REG_P (node->loc)
2895 && REGNO (node2->loc) == REGNO (node->loc))
2896 || rtx_equal_p (node2->loc, node->loc)))
2898 if (node2->init < node->init)
2899 node2->init = node->init;
2900 break;
2903 if (node || node2)
2905 dstp = unshare_variable (set, dstp, dst,
2906 VAR_INIT_STATUS_UNKNOWN);
2907 dst = (variable *)*dstp;
2911 src_l = 0;
2912 for (node = src->var_part[i].loc_chain; node; node = node->next)
2913 src_l++;
2914 dst_l = 0;
2915 for (node = dst->var_part[j].loc_chain; node; node = node->next)
2916 dst_l++;
2918 if (dst_l == 1)
2920 /* The most common case, much simpler, no qsort is needed. */
2921 location_chain *dstnode = dst->var_part[j].loc_chain;
2922 dst->var_part[k].loc_chain = dstnode;
2923 VAR_PART_OFFSET (dst, k) = VAR_PART_OFFSET (dst, j);
2924 node2 = dstnode;
2925 for (node = src->var_part[i].loc_chain; node; node = node->next)
2926 if (!((REG_P (dstnode->loc)
2927 && REG_P (node->loc)
2928 && REGNO (dstnode->loc) == REGNO (node->loc))
2929 || rtx_equal_p (dstnode->loc, node->loc)))
2931 location_chain *new_node;
2933 /* Copy the location from SRC. */
2934 new_node = new location_chain;
2935 new_node->loc = node->loc;
2936 new_node->init = node->init;
2937 if (!node->set_src || MEM_P (node->set_src))
2938 new_node->set_src = NULL;
2939 else
2940 new_node->set_src = node->set_src;
2941 node2->next = new_node;
2942 node2 = new_node;
2944 node2->next = NULL;
2946 else
2948 if (src_l + dst_l > vui_allocated)
2950 vui_allocated = MAX (vui_allocated * 2, src_l + dst_l);
2951 vui_vec = XRESIZEVEC (struct variable_union_info, vui_vec,
2952 vui_allocated);
2954 vui = vui_vec;
2956 /* Fill in the locations from DST. */
2957 for (node = dst->var_part[j].loc_chain, jj = 0; node;
2958 node = node->next, jj++)
2960 vui[jj].lc = node;
2961 vui[jj].pos_dst = jj;
2963 /* Pos plus value larger than a sum of 2 valid positions. */
2964 vui[jj].pos = jj + src_l + dst_l;
2967 /* Fill in the locations from SRC. */
2968 n = dst_l;
2969 for (node = src->var_part[i].loc_chain, ii = 0; node;
2970 node = node->next, ii++)
2972 /* Find location from NODE. */
2973 for (jj = 0; jj < dst_l; jj++)
2975 if ((REG_P (vui[jj].lc->loc)
2976 && REG_P (node->loc)
2977 && REGNO (vui[jj].lc->loc) == REGNO (node->loc))
2978 || rtx_equal_p (vui[jj].lc->loc, node->loc))
2980 vui[jj].pos = jj + ii;
2981 break;
2984 if (jj >= dst_l) /* The location has not been found. */
2986 location_chain *new_node;
2988 /* Copy the location from SRC. */
2989 new_node = new location_chain;
2990 new_node->loc = node->loc;
2991 new_node->init = node->init;
2992 if (!node->set_src || MEM_P (node->set_src))
2993 new_node->set_src = NULL;
2994 else
2995 new_node->set_src = node->set_src;
2996 vui[n].lc = new_node;
2997 vui[n].pos_dst = src_l + dst_l;
2998 vui[n].pos = ii + src_l + dst_l;
2999 n++;
3003 if (dst_l == 2)
3005 /* Special case still very common case. For dst_l == 2
3006 all entries dst_l ... n-1 are sorted, with for i >= dst_l
3007 vui[i].pos == i + src_l + dst_l. */
3008 if (vui[0].pos > vui[1].pos)
3010 /* Order should be 1, 0, 2... */
3011 dst->var_part[k].loc_chain = vui[1].lc;
3012 vui[1].lc->next = vui[0].lc;
3013 if (n >= 3)
3015 vui[0].lc->next = vui[2].lc;
3016 vui[n - 1].lc->next = NULL;
3018 else
3019 vui[0].lc->next = NULL;
3020 ii = 3;
3022 else
3024 dst->var_part[k].loc_chain = vui[0].lc;
3025 if (n >= 3 && vui[2].pos < vui[1].pos)
3027 /* Order should be 0, 2, 1, 3... */
3028 vui[0].lc->next = vui[2].lc;
3029 vui[2].lc->next = vui[1].lc;
3030 if (n >= 4)
3032 vui[1].lc->next = vui[3].lc;
3033 vui[n - 1].lc->next = NULL;
3035 else
3036 vui[1].lc->next = NULL;
3037 ii = 4;
3039 else
3041 /* Order should be 0, 1, 2... */
3042 ii = 1;
3043 vui[n - 1].lc->next = NULL;
3046 for (; ii < n; ii++)
3047 vui[ii - 1].lc->next = vui[ii].lc;
3049 else
3051 qsort (vui, n, sizeof (struct variable_union_info),
3052 variable_union_info_cmp_pos);
3054 /* Reconnect the nodes in sorted order. */
3055 for (ii = 1; ii < n; ii++)
3056 vui[ii - 1].lc->next = vui[ii].lc;
3057 vui[n - 1].lc->next = NULL;
3058 dst->var_part[k].loc_chain = vui[0].lc;
3061 VAR_PART_OFFSET (dst, k) = VAR_PART_OFFSET (dst, j);
3063 i--;
3064 j--;
3066 else if ((i >= 0 && j >= 0
3067 && VAR_PART_OFFSET (src, i) < VAR_PART_OFFSET (dst, j))
3068 || i < 0)
3070 dst->var_part[k] = dst->var_part[j];
3071 j--;
3073 else if ((i >= 0 && j >= 0
3074 && VAR_PART_OFFSET (src, i) > VAR_PART_OFFSET (dst, j))
3075 || j < 0)
3077 location_chain **nextp;
3079 /* Copy the chain from SRC. */
3080 nextp = &dst->var_part[k].loc_chain;
3081 for (node = src->var_part[i].loc_chain; node; node = node->next)
3083 location_chain *new_lc;
3085 new_lc = new location_chain;
3086 new_lc->next = NULL;
3087 new_lc->init = node->init;
3088 if (!node->set_src || MEM_P (node->set_src))
3089 new_lc->set_src = NULL;
3090 else
3091 new_lc->set_src = node->set_src;
3092 new_lc->loc = node->loc;
3094 *nextp = new_lc;
3095 nextp = &new_lc->next;
3098 VAR_PART_OFFSET (dst, k) = VAR_PART_OFFSET (src, i);
3099 i--;
3101 dst->var_part[k].cur_loc = NULL;
3104 if (flag_var_tracking_uninit)
3105 for (i = 0; i < src->n_var_parts && i < dst->n_var_parts; i++)
3107 location_chain *node, *node2;
3108 for (node = src->var_part[i].loc_chain; node; node = node->next)
3109 for (node2 = dst->var_part[i].loc_chain; node2; node2 = node2->next)
3110 if (rtx_equal_p (node->loc, node2->loc))
3112 if (node->init > node2->init)
3113 node2->init = node->init;
3117 /* Continue traversing the hash table. */
3118 return 1;
3121 /* Compute union of dataflow sets SRC and DST and store it to DST. */
3123 static void
3124 dataflow_set_union (dataflow_set *dst, dataflow_set *src)
3126 int i;
3128 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
3129 attrs_list_union (&dst->regs[i], src->regs[i]);
3131 if (dst->vars == empty_shared_hash)
3133 shared_hash_destroy (dst->vars);
3134 dst->vars = shared_hash_copy (src->vars);
3136 else
3138 variable_iterator_type hi;
3139 variable *var;
3141 FOR_EACH_HASH_TABLE_ELEMENT (*shared_hash_htab (src->vars),
3142 var, variable, hi)
3143 variable_union (var, dst);
3147 /* Whether the value is currently being expanded. */
3148 #define VALUE_RECURSED_INTO(x) \
3149 (RTL_FLAG_CHECK2 ("VALUE_RECURSED_INTO", (x), VALUE, DEBUG_EXPR)->used)
3151 /* Whether no expansion was found, saving useless lookups.
3152 It must only be set when VALUE_CHANGED is clear. */
3153 #define NO_LOC_P(x) \
3154 (RTL_FLAG_CHECK2 ("NO_LOC_P", (x), VALUE, DEBUG_EXPR)->return_val)
3156 /* Whether cur_loc in the value needs to be (re)computed. */
3157 #define VALUE_CHANGED(x) \
3158 (RTL_FLAG_CHECK1 ("VALUE_CHANGED", (x), VALUE)->frame_related)
3159 /* Whether cur_loc in the decl needs to be (re)computed. */
3160 #define DECL_CHANGED(x) TREE_VISITED (x)
3162 /* Record (if NEWV) that DV needs to have its cur_loc recomputed. For
3163 user DECLs, this means they're in changed_variables. Values and
3164 debug exprs may be left with this flag set if no user variable
3165 requires them to be evaluated. */
3167 static inline void
3168 set_dv_changed (decl_or_value dv, bool newv)
3170 switch (dv_onepart_p (dv))
3172 case ONEPART_VALUE:
3173 if (newv)
3174 NO_LOC_P (dv_as_value (dv)) = false;
3175 VALUE_CHANGED (dv_as_value (dv)) = newv;
3176 break;
3178 case ONEPART_DEXPR:
3179 if (newv)
3180 NO_LOC_P (DECL_RTL_KNOWN_SET (dv_as_decl (dv))) = false;
3181 /* Fall through. */
3183 default:
3184 DECL_CHANGED (dv_as_decl (dv)) = newv;
3185 break;
3189 /* Return true if DV needs to have its cur_loc recomputed. */
3191 static inline bool
3192 dv_changed_p (decl_or_value dv)
3194 return (dv_is_value_p (dv)
3195 ? VALUE_CHANGED (dv_as_value (dv))
3196 : DECL_CHANGED (dv_as_decl (dv)));
3199 /* Return a location list node whose loc is rtx_equal to LOC, in the
3200 location list of a one-part variable or value VAR, or in that of
3201 any values recursively mentioned in the location lists. VARS must
3202 be in star-canonical form. */
3204 static location_chain *
3205 find_loc_in_1pdv (rtx loc, variable *var, variable_table_type *vars)
3207 location_chain *node;
3208 enum rtx_code loc_code;
3210 if (!var)
3211 return NULL;
3213 gcc_checking_assert (var->onepart);
3215 if (!var->n_var_parts)
3216 return NULL;
3218 gcc_checking_assert (loc != dv_as_opaque (var->dv));
3220 loc_code = GET_CODE (loc);
3221 for (node = var->var_part[0].loc_chain; node; node = node->next)
3223 decl_or_value dv;
3224 variable *rvar;
3226 if (GET_CODE (node->loc) != loc_code)
3228 if (GET_CODE (node->loc) != VALUE)
3229 continue;
3231 else if (loc == node->loc)
3232 return node;
3233 else if (loc_code != VALUE)
3235 if (rtx_equal_p (loc, node->loc))
3236 return node;
3237 continue;
3240 /* Since we're in star-canonical form, we don't need to visit
3241 non-canonical nodes: one-part variables and non-canonical
3242 values would only point back to the canonical node. */
3243 if (dv_is_value_p (var->dv)
3244 && !canon_value_cmp (node->loc, dv_as_value (var->dv)))
3246 /* Skip all subsequent VALUEs. */
3247 while (node->next && GET_CODE (node->next->loc) == VALUE)
3249 node = node->next;
3250 gcc_checking_assert (!canon_value_cmp (node->loc,
3251 dv_as_value (var->dv)));
3252 if (loc == node->loc)
3253 return node;
3255 continue;
3258 gcc_checking_assert (node == var->var_part[0].loc_chain);
3259 gcc_checking_assert (!node->next);
3261 dv = dv_from_value (node->loc);
3262 rvar = vars->find_with_hash (dv, dv_htab_hash (dv));
3263 return find_loc_in_1pdv (loc, rvar, vars);
3266 /* ??? Gotta look in cselib_val locations too. */
3268 return NULL;
3271 /* Hash table iteration argument passed to variable_merge. */
3272 struct dfset_merge
3274 /* The set in which the merge is to be inserted. */
3275 dataflow_set *dst;
3276 /* The set that we're iterating in. */
3277 dataflow_set *cur;
3278 /* The set that may contain the other dv we are to merge with. */
3279 dataflow_set *src;
3280 /* Number of onepart dvs in src. */
3281 int src_onepart_cnt;
3284 /* Insert LOC in *DNODE, if it's not there yet. The list must be in
3285 loc_cmp order, and it is maintained as such. */
3287 static void
3288 insert_into_intersection (location_chain **nodep, rtx loc,
3289 enum var_init_status status)
3291 location_chain *node;
3292 int r;
3294 for (node = *nodep; node; nodep = &node->next, node = *nodep)
3295 if ((r = loc_cmp (node->loc, loc)) == 0)
3297 node->init = MIN (node->init, status);
3298 return;
3300 else if (r > 0)
3301 break;
3303 node = new location_chain;
3305 node->loc = loc;
3306 node->set_src = NULL;
3307 node->init = status;
3308 node->next = *nodep;
3309 *nodep = node;
3312 /* Insert in DEST the intersection of the locations present in both
3313 S1NODE and S2VAR, directly or indirectly. S1NODE is from a
3314 variable in DSM->cur, whereas S2VAR is from DSM->src. dvar is in
3315 DSM->dst. */
3317 static void
3318 intersect_loc_chains (rtx val, location_chain **dest, struct dfset_merge *dsm,
3319 location_chain *s1node, variable *s2var)
3321 dataflow_set *s1set = dsm->cur;
3322 dataflow_set *s2set = dsm->src;
3323 location_chain *found;
3325 if (s2var)
3327 location_chain *s2node;
3329 gcc_checking_assert (s2var->onepart);
3331 if (s2var->n_var_parts)
3333 s2node = s2var->var_part[0].loc_chain;
3335 for (; s1node && s2node;
3336 s1node = s1node->next, s2node = s2node->next)
3337 if (s1node->loc != s2node->loc)
3338 break;
3339 else if (s1node->loc == val)
3340 continue;
3341 else
3342 insert_into_intersection (dest, s1node->loc,
3343 MIN (s1node->init, s2node->init));
3347 for (; s1node; s1node = s1node->next)
3349 if (s1node->loc == val)
3350 continue;
3352 if ((found = find_loc_in_1pdv (s1node->loc, s2var,
3353 shared_hash_htab (s2set->vars))))
3355 insert_into_intersection (dest, s1node->loc,
3356 MIN (s1node->init, found->init));
3357 continue;
3360 if (GET_CODE (s1node->loc) == VALUE
3361 && !VALUE_RECURSED_INTO (s1node->loc))
3363 decl_or_value dv = dv_from_value (s1node->loc);
3364 variable *svar = shared_hash_find (s1set->vars, dv);
3365 if (svar)
3367 if (svar->n_var_parts == 1)
3369 VALUE_RECURSED_INTO (s1node->loc) = true;
3370 intersect_loc_chains (val, dest, dsm,
3371 svar->var_part[0].loc_chain,
3372 s2var);
3373 VALUE_RECURSED_INTO (s1node->loc) = false;
3378 /* ??? gotta look in cselib_val locations too. */
3380 /* ??? if the location is equivalent to any location in src,
3381 searched recursively
3383 add to dst the values needed to represent the equivalence
3385 telling whether locations S is equivalent to another dv's
3386 location list:
3388 for each location D in the list
3390 if S and D satisfy rtx_equal_p, then it is present
3392 else if D is a value, recurse without cycles
3394 else if S and D have the same CODE and MODE
3396 for each operand oS and the corresponding oD
3398 if oS and oD are not equivalent, then S an D are not equivalent
3400 else if they are RTX vectors
3402 if any vector oS element is not equivalent to its respective oD,
3403 then S and D are not equivalent
3411 /* Return -1 if X should be before Y in a location list for a 1-part
3412 variable, 1 if Y should be before X, and 0 if they're equivalent
3413 and should not appear in the list. */
3415 static int
3416 loc_cmp (rtx x, rtx y)
3418 int i, j, r;
3419 RTX_CODE code = GET_CODE (x);
3420 const char *fmt;
3422 if (x == y)
3423 return 0;
3425 if (REG_P (x))
3427 if (!REG_P (y))
3428 return -1;
3429 gcc_assert (GET_MODE (x) == GET_MODE (y));
3430 if (REGNO (x) == REGNO (y))
3431 return 0;
3432 else if (REGNO (x) < REGNO (y))
3433 return -1;
3434 else
3435 return 1;
3438 if (REG_P (y))
3439 return 1;
3441 if (MEM_P (x))
3443 if (!MEM_P (y))
3444 return -1;
3445 gcc_assert (GET_MODE (x) == GET_MODE (y));
3446 return loc_cmp (XEXP (x, 0), XEXP (y, 0));
3449 if (MEM_P (y))
3450 return 1;
3452 if (GET_CODE (x) == VALUE)
3454 if (GET_CODE (y) != VALUE)
3455 return -1;
3456 /* Don't assert the modes are the same, that is true only
3457 when not recursing. (subreg:QI (value:SI 1:1) 0)
3458 and (subreg:QI (value:DI 2:2) 0) can be compared,
3459 even when the modes are different. */
3460 if (canon_value_cmp (x, y))
3461 return -1;
3462 else
3463 return 1;
3466 if (GET_CODE (y) == VALUE)
3467 return 1;
3469 /* Entry value is the least preferable kind of expression. */
3470 if (GET_CODE (x) == ENTRY_VALUE)
3472 if (GET_CODE (y) != ENTRY_VALUE)
3473 return 1;
3474 gcc_assert (GET_MODE (x) == GET_MODE (y));
3475 return loc_cmp (ENTRY_VALUE_EXP (x), ENTRY_VALUE_EXP (y));
3478 if (GET_CODE (y) == ENTRY_VALUE)
3479 return -1;
3481 if (GET_CODE (x) == GET_CODE (y))
3482 /* Compare operands below. */;
3483 else if (GET_CODE (x) < GET_CODE (y))
3484 return -1;
3485 else
3486 return 1;
3488 gcc_assert (GET_MODE (x) == GET_MODE (y));
3490 if (GET_CODE (x) == DEBUG_EXPR)
3492 if (DEBUG_TEMP_UID (DEBUG_EXPR_TREE_DECL (x))
3493 < DEBUG_TEMP_UID (DEBUG_EXPR_TREE_DECL (y)))
3494 return -1;
3495 gcc_checking_assert (DEBUG_TEMP_UID (DEBUG_EXPR_TREE_DECL (x))
3496 > DEBUG_TEMP_UID (DEBUG_EXPR_TREE_DECL (y)));
3497 return 1;
3500 fmt = GET_RTX_FORMAT (code);
3501 for (i = 0; i < GET_RTX_LENGTH (code); i++)
3502 switch (fmt[i])
3504 case 'w':
3505 if (XWINT (x, i) == XWINT (y, i))
3506 break;
3507 else if (XWINT (x, i) < XWINT (y, i))
3508 return -1;
3509 else
3510 return 1;
3512 case 'n':
3513 case 'i':
3514 if (XINT (x, i) == XINT (y, i))
3515 break;
3516 else if (XINT (x, i) < XINT (y, i))
3517 return -1;
3518 else
3519 return 1;
3521 case 'p':
3522 r = compare_sizes_for_sort (SUBREG_BYTE (x), SUBREG_BYTE (y));
3523 if (r != 0)
3524 return r;
3525 break;
3527 case 'V':
3528 case 'E':
3529 /* Compare the vector length first. */
3530 if (XVECLEN (x, i) == XVECLEN (y, i))
3531 /* Compare the vectors elements. */;
3532 else if (XVECLEN (x, i) < XVECLEN (y, i))
3533 return -1;
3534 else
3535 return 1;
3537 for (j = 0; j < XVECLEN (x, i); j++)
3538 if ((r = loc_cmp (XVECEXP (x, i, j),
3539 XVECEXP (y, i, j))))
3540 return r;
3541 break;
3543 case 'e':
3544 if ((r = loc_cmp (XEXP (x, i), XEXP (y, i))))
3545 return r;
3546 break;
3548 case 'S':
3549 case 's':
3550 if (XSTR (x, i) == XSTR (y, i))
3551 break;
3552 if (!XSTR (x, i))
3553 return -1;
3554 if (!XSTR (y, i))
3555 return 1;
3556 if ((r = strcmp (XSTR (x, i), XSTR (y, i))) == 0)
3557 break;
3558 else if (r < 0)
3559 return -1;
3560 else
3561 return 1;
3563 case 'u':
3564 /* These are just backpointers, so they don't matter. */
3565 break;
3567 case '0':
3568 case 't':
3569 break;
3571 /* It is believed that rtx's at this level will never
3572 contain anything but integers and other rtx's,
3573 except for within LABEL_REFs and SYMBOL_REFs. */
3574 default:
3575 gcc_unreachable ();
3577 if (CONST_WIDE_INT_P (x))
3579 /* Compare the vector length first. */
3580 if (CONST_WIDE_INT_NUNITS (x) >= CONST_WIDE_INT_NUNITS (y))
3581 return 1;
3582 else if (CONST_WIDE_INT_NUNITS (x) < CONST_WIDE_INT_NUNITS (y))
3583 return -1;
3585 /* Compare the vectors elements. */;
3586 for (j = CONST_WIDE_INT_NUNITS (x) - 1; j >= 0 ; j--)
3588 if (CONST_WIDE_INT_ELT (x, j) < CONST_WIDE_INT_ELT (y, j))
3589 return -1;
3590 if (CONST_WIDE_INT_ELT (x, j) > CONST_WIDE_INT_ELT (y, j))
3591 return 1;
3595 return 0;
3598 /* Check the order of entries in one-part variables. */
3601 canonicalize_loc_order_check (variable **slot,
3602 dataflow_set *data ATTRIBUTE_UNUSED)
3604 variable *var = *slot;
3605 location_chain *node, *next;
3607 #ifdef ENABLE_RTL_CHECKING
3608 int i;
3609 for (i = 0; i < var->n_var_parts; i++)
3610 gcc_assert (var->var_part[0].cur_loc == NULL);
3611 gcc_assert (!var->in_changed_variables);
3612 #endif
3614 if (!var->onepart)
3615 return 1;
3617 gcc_assert (var->n_var_parts == 1);
3618 node = var->var_part[0].loc_chain;
3619 gcc_assert (node);
3621 while ((next = node->next))
3623 gcc_assert (loc_cmp (node->loc, next->loc) < 0);
3624 node = next;
3627 return 1;
3630 /* Mark with VALUE_RECURSED_INTO values that have neighbors that are
3631 more likely to be chosen as canonical for an equivalence set.
3632 Ensure less likely values can reach more likely neighbors, making
3633 the connections bidirectional. */
3636 canonicalize_values_mark (variable **slot, dataflow_set *set)
3638 variable *var = *slot;
3639 decl_or_value dv = var->dv;
3640 rtx val;
3641 location_chain *node;
3643 if (!dv_is_value_p (dv))
3644 return 1;
3646 gcc_checking_assert (var->n_var_parts == 1);
3648 val = dv_as_value (dv);
3650 for (node = var->var_part[0].loc_chain; node; node = node->next)
3651 if (GET_CODE (node->loc) == VALUE)
3653 if (canon_value_cmp (node->loc, val))
3654 VALUE_RECURSED_INTO (val) = true;
3655 else
3657 decl_or_value odv = dv_from_value (node->loc);
3658 variable **oslot;
3659 oslot = shared_hash_find_slot_noinsert (set->vars, odv);
3661 set_slot_part (set, val, oslot, odv, 0,
3662 node->init, NULL_RTX);
3664 VALUE_RECURSED_INTO (node->loc) = true;
3668 return 1;
3671 /* Remove redundant entries from equivalence lists in onepart
3672 variables, canonicalizing equivalence sets into star shapes. */
3675 canonicalize_values_star (variable **slot, dataflow_set *set)
3677 variable *var = *slot;
3678 decl_or_value dv = var->dv;
3679 location_chain *node;
3680 decl_or_value cdv;
3681 rtx val, cval;
3682 variable **cslot;
3683 bool has_value;
3684 bool has_marks;
3686 if (!var->onepart)
3687 return 1;
3689 gcc_checking_assert (var->n_var_parts == 1);
3691 if (dv_is_value_p (dv))
3693 cval = dv_as_value (dv);
3694 if (!VALUE_RECURSED_INTO (cval))
3695 return 1;
3696 VALUE_RECURSED_INTO (cval) = false;
3698 else
3699 cval = NULL_RTX;
3701 restart:
3702 val = cval;
3703 has_value = false;
3704 has_marks = false;
3706 gcc_assert (var->n_var_parts == 1);
3708 for (node = var->var_part[0].loc_chain; node; node = node->next)
3709 if (GET_CODE (node->loc) == VALUE)
3711 has_value = true;
3712 if (VALUE_RECURSED_INTO (node->loc))
3713 has_marks = true;
3714 if (canon_value_cmp (node->loc, cval))
3715 cval = node->loc;
3718 if (!has_value)
3719 return 1;
3721 if (cval == val)
3723 if (!has_marks || dv_is_decl_p (dv))
3724 return 1;
3726 /* Keep it marked so that we revisit it, either after visiting a
3727 child node, or after visiting a new parent that might be
3728 found out. */
3729 VALUE_RECURSED_INTO (val) = true;
3731 for (node = var->var_part[0].loc_chain; node; node = node->next)
3732 if (GET_CODE (node->loc) == VALUE
3733 && VALUE_RECURSED_INTO (node->loc))
3735 cval = node->loc;
3736 restart_with_cval:
3737 VALUE_RECURSED_INTO (cval) = false;
3738 dv = dv_from_value (cval);
3739 slot = shared_hash_find_slot_noinsert (set->vars, dv);
3740 if (!slot)
3742 gcc_assert (dv_is_decl_p (var->dv));
3743 /* The canonical value was reset and dropped.
3744 Remove it. */
3745 clobber_variable_part (set, NULL, var->dv, 0, NULL);
3746 return 1;
3748 var = *slot;
3749 gcc_assert (dv_is_value_p (var->dv));
3750 if (var->n_var_parts == 0)
3751 return 1;
3752 gcc_assert (var->n_var_parts == 1);
3753 goto restart;
3756 VALUE_RECURSED_INTO (val) = false;
3758 return 1;
3761 /* Push values to the canonical one. */
3762 cdv = dv_from_value (cval);
3763 cslot = shared_hash_find_slot_noinsert (set->vars, cdv);
3765 for (node = var->var_part[0].loc_chain; node; node = node->next)
3766 if (node->loc != cval)
3768 cslot = set_slot_part (set, node->loc, cslot, cdv, 0,
3769 node->init, NULL_RTX);
3770 if (GET_CODE (node->loc) == VALUE)
3772 decl_or_value ndv = dv_from_value (node->loc);
3774 set_variable_part (set, cval, ndv, 0, node->init, NULL_RTX,
3775 NO_INSERT);
3777 if (canon_value_cmp (node->loc, val))
3779 /* If it could have been a local minimum, it's not any more,
3780 since it's now neighbor to cval, so it may have to push
3781 to it. Conversely, if it wouldn't have prevailed over
3782 val, then whatever mark it has is fine: if it was to
3783 push, it will now push to a more canonical node, but if
3784 it wasn't, then it has already pushed any values it might
3785 have to. */
3786 VALUE_RECURSED_INTO (node->loc) = true;
3787 /* Make sure we visit node->loc by ensuring we cval is
3788 visited too. */
3789 VALUE_RECURSED_INTO (cval) = true;
3791 else if (!VALUE_RECURSED_INTO (node->loc))
3792 /* If we have no need to "recurse" into this node, it's
3793 already "canonicalized", so drop the link to the old
3794 parent. */
3795 clobber_variable_part (set, cval, ndv, 0, NULL);
3797 else if (GET_CODE (node->loc) == REG)
3799 attrs *list = set->regs[REGNO (node->loc)], **listp;
3801 /* Change an existing attribute referring to dv so that it
3802 refers to cdv, removing any duplicate this might
3803 introduce, and checking that no previous duplicates
3804 existed, all in a single pass. */
3806 while (list)
3808 if (list->offset == 0
3809 && (dv_as_opaque (list->dv) == dv_as_opaque (dv)
3810 || dv_as_opaque (list->dv) == dv_as_opaque (cdv)))
3811 break;
3813 list = list->next;
3816 gcc_assert (list);
3817 if (dv_as_opaque (list->dv) == dv_as_opaque (dv))
3819 list->dv = cdv;
3820 for (listp = &list->next; (list = *listp); listp = &list->next)
3822 if (list->offset)
3823 continue;
3825 if (dv_as_opaque (list->dv) == dv_as_opaque (cdv))
3827 *listp = list->next;
3828 delete list;
3829 list = *listp;
3830 break;
3833 gcc_assert (dv_as_opaque (list->dv) != dv_as_opaque (dv));
3836 else if (dv_as_opaque (list->dv) == dv_as_opaque (cdv))
3838 for (listp = &list->next; (list = *listp); listp = &list->next)
3840 if (list->offset)
3841 continue;
3843 if (dv_as_opaque (list->dv) == dv_as_opaque (dv))
3845 *listp = list->next;
3846 delete list;
3847 list = *listp;
3848 break;
3851 gcc_assert (dv_as_opaque (list->dv) != dv_as_opaque (cdv));
3854 else
3855 gcc_unreachable ();
3857 if (flag_checking)
3858 while (list)
3860 if (list->offset == 0
3861 && (dv_as_opaque (list->dv) == dv_as_opaque (dv)
3862 || dv_as_opaque (list->dv) == dv_as_opaque (cdv)))
3863 gcc_unreachable ();
3865 list = list->next;
3870 if (val)
3871 set_slot_part (set, val, cslot, cdv, 0,
3872 VAR_INIT_STATUS_INITIALIZED, NULL_RTX);
3874 slot = clobber_slot_part (set, cval, slot, 0, NULL);
3876 /* Variable may have been unshared. */
3877 var = *slot;
3878 gcc_checking_assert (var->n_var_parts && var->var_part[0].loc_chain->loc == cval
3879 && var->var_part[0].loc_chain->next == NULL);
3881 if (VALUE_RECURSED_INTO (cval))
3882 goto restart_with_cval;
3884 return 1;
3887 /* Bind one-part variables to the canonical value in an equivalence
3888 set. Not doing this causes dataflow convergence failure in rare
3889 circumstances, see PR42873. Unfortunately we can't do this
3890 efficiently as part of canonicalize_values_star, since we may not
3891 have determined or even seen the canonical value of a set when we
3892 get to a variable that references another member of the set. */
3895 canonicalize_vars_star (variable **slot, dataflow_set *set)
3897 variable *var = *slot;
3898 decl_or_value dv = var->dv;
3899 location_chain *node;
3900 rtx cval;
3901 decl_or_value cdv;
3902 variable **cslot;
3903 variable *cvar;
3904 location_chain *cnode;
3906 if (!var->onepart || var->onepart == ONEPART_VALUE)
3907 return 1;
3909 gcc_assert (var->n_var_parts == 1);
3911 node = var->var_part[0].loc_chain;
3913 if (GET_CODE (node->loc) != VALUE)
3914 return 1;
3916 gcc_assert (!node->next);
3917 cval = node->loc;
3919 /* Push values to the canonical one. */
3920 cdv = dv_from_value (cval);
3921 cslot = shared_hash_find_slot_noinsert (set->vars, cdv);
3922 if (!cslot)
3923 return 1;
3924 cvar = *cslot;
3925 gcc_assert (cvar->n_var_parts == 1);
3927 cnode = cvar->var_part[0].loc_chain;
3929 /* CVAL is canonical if its value list contains non-VALUEs or VALUEs
3930 that are not “more canonical” than it. */
3931 if (GET_CODE (cnode->loc) != VALUE
3932 || !canon_value_cmp (cnode->loc, cval))
3933 return 1;
3935 /* CVAL was found to be non-canonical. Change the variable to point
3936 to the canonical VALUE. */
3937 gcc_assert (!cnode->next);
3938 cval = cnode->loc;
3940 slot = set_slot_part (set, cval, slot, dv, 0,
3941 node->init, node->set_src);
3942 clobber_slot_part (set, cval, slot, 0, node->set_src);
3944 return 1;
3947 /* Combine variable or value in *S1SLOT (in DSM->cur) with the
3948 corresponding entry in DSM->src. Multi-part variables are combined
3949 with variable_union, whereas onepart dvs are combined with
3950 intersection. */
3952 static int
3953 variable_merge_over_cur (variable *s1var, struct dfset_merge *dsm)
3955 dataflow_set *dst = dsm->dst;
3956 variable **dstslot;
3957 variable *s2var, *dvar = NULL;
3958 decl_or_value dv = s1var->dv;
3959 onepart_enum onepart = s1var->onepart;
3960 rtx val;
3961 hashval_t dvhash;
3962 location_chain *node, **nodep;
3964 /* If the incoming onepart variable has an empty location list, then
3965 the intersection will be just as empty. For other variables,
3966 it's always union. */
3967 gcc_checking_assert (s1var->n_var_parts
3968 && s1var->var_part[0].loc_chain);
3970 if (!onepart)
3971 return variable_union (s1var, dst);
3973 gcc_checking_assert (s1var->n_var_parts == 1);
3975 dvhash = dv_htab_hash (dv);
3976 if (dv_is_value_p (dv))
3977 val = dv_as_value (dv);
3978 else
3979 val = NULL;
3981 s2var = shared_hash_find_1 (dsm->src->vars, dv, dvhash);
3982 if (!s2var)
3984 dst_can_be_shared = false;
3985 return 1;
3988 dsm->src_onepart_cnt--;
3989 gcc_assert (s2var->var_part[0].loc_chain
3990 && s2var->onepart == onepart
3991 && s2var->n_var_parts == 1);
3993 dstslot = shared_hash_find_slot_noinsert_1 (dst->vars, dv, dvhash);
3994 if (dstslot)
3996 dvar = *dstslot;
3997 gcc_assert (dvar->refcount == 1
3998 && dvar->onepart == onepart
3999 && dvar->n_var_parts == 1);
4000 nodep = &dvar->var_part[0].loc_chain;
4002 else
4004 nodep = &node;
4005 node = NULL;
4008 if (!dstslot && !onepart_variable_different_p (s1var, s2var))
4010 dstslot = shared_hash_find_slot_unshare_1 (&dst->vars, dv,
4011 dvhash, INSERT);
4012 *dstslot = dvar = s2var;
4013 dvar->refcount++;
4015 else
4017 dst_can_be_shared = false;
4019 intersect_loc_chains (val, nodep, dsm,
4020 s1var->var_part[0].loc_chain, s2var);
4022 if (!dstslot)
4024 if (node)
4026 dvar = onepart_pool_allocate (onepart);
4027 dvar->dv = dv;
4028 dvar->refcount = 1;
4029 dvar->n_var_parts = 1;
4030 dvar->onepart = onepart;
4031 dvar->in_changed_variables = false;
4032 dvar->var_part[0].loc_chain = node;
4033 dvar->var_part[0].cur_loc = NULL;
4034 if (onepart)
4035 VAR_LOC_1PAUX (dvar) = NULL;
4036 else
4037 VAR_PART_OFFSET (dvar, 0) = 0;
4039 dstslot
4040 = shared_hash_find_slot_unshare_1 (&dst->vars, dv, dvhash,
4041 INSERT);
4042 gcc_assert (!*dstslot);
4043 *dstslot = dvar;
4045 else
4046 return 1;
4050 nodep = &dvar->var_part[0].loc_chain;
4051 while ((node = *nodep))
4053 location_chain **nextp = &node->next;
4055 if (GET_CODE (node->loc) == REG)
4057 attrs *list;
4059 for (list = dst->regs[REGNO (node->loc)]; list; list = list->next)
4060 if (GET_MODE (node->loc) == GET_MODE (list->loc)
4061 && dv_is_value_p (list->dv))
4062 break;
4064 if (!list)
4065 attrs_list_insert (&dst->regs[REGNO (node->loc)],
4066 dv, 0, node->loc);
4067 /* If this value became canonical for another value that had
4068 this register, we want to leave it alone. */
4069 else if (dv_as_value (list->dv) != val)
4071 dstslot = set_slot_part (dst, dv_as_value (list->dv),
4072 dstslot, dv, 0,
4073 node->init, NULL_RTX);
4074 dstslot = delete_slot_part (dst, node->loc, dstslot, 0);
4076 /* Since nextp points into the removed node, we can't
4077 use it. The pointer to the next node moved to nodep.
4078 However, if the variable we're walking is unshared
4079 during our walk, we'll keep walking the location list
4080 of the previously-shared variable, in which case the
4081 node won't have been removed, and we'll want to skip
4082 it. That's why we test *nodep here. */
4083 if (*nodep != node)
4084 nextp = nodep;
4087 else
4088 /* Canonicalization puts registers first, so we don't have to
4089 walk it all. */
4090 break;
4091 nodep = nextp;
4094 if (dvar != *dstslot)
4095 dvar = *dstslot;
4096 nodep = &dvar->var_part[0].loc_chain;
4098 if (val)
4100 /* Mark all referenced nodes for canonicalization, and make sure
4101 we have mutual equivalence links. */
4102 VALUE_RECURSED_INTO (val) = true;
4103 for (node = *nodep; node; node = node->next)
4104 if (GET_CODE (node->loc) == VALUE)
4106 VALUE_RECURSED_INTO (node->loc) = true;
4107 set_variable_part (dst, val, dv_from_value (node->loc), 0,
4108 node->init, NULL, INSERT);
4111 dstslot = shared_hash_find_slot_noinsert_1 (dst->vars, dv, dvhash);
4112 gcc_assert (*dstslot == dvar);
4113 canonicalize_values_star (dstslot, dst);
4114 gcc_checking_assert (dstslot
4115 == shared_hash_find_slot_noinsert_1 (dst->vars,
4116 dv, dvhash));
4117 dvar = *dstslot;
4119 else
4121 bool has_value = false, has_other = false;
4123 /* If we have one value and anything else, we're going to
4124 canonicalize this, so make sure all values have an entry in
4125 the table and are marked for canonicalization. */
4126 for (node = *nodep; node; node = node->next)
4128 if (GET_CODE (node->loc) == VALUE)
4130 /* If this was marked during register canonicalization,
4131 we know we have to canonicalize values. */
4132 if (has_value)
4133 has_other = true;
4134 has_value = true;
4135 if (has_other)
4136 break;
4138 else
4140 has_other = true;
4141 if (has_value)
4142 break;
4146 if (has_value && has_other)
4148 for (node = *nodep; node; node = node->next)
4150 if (GET_CODE (node->loc) == VALUE)
4152 decl_or_value dv = dv_from_value (node->loc);
4153 variable **slot = NULL;
4155 if (shared_hash_shared (dst->vars))
4156 slot = shared_hash_find_slot_noinsert (dst->vars, dv);
4157 if (!slot)
4158 slot = shared_hash_find_slot_unshare (&dst->vars, dv,
4159 INSERT);
4160 if (!*slot)
4162 variable *var = onepart_pool_allocate (ONEPART_VALUE);
4163 var->dv = dv;
4164 var->refcount = 1;
4165 var->n_var_parts = 1;
4166 var->onepart = ONEPART_VALUE;
4167 var->in_changed_variables = false;
4168 var->var_part[0].loc_chain = NULL;
4169 var->var_part[0].cur_loc = NULL;
4170 VAR_LOC_1PAUX (var) = NULL;
4171 *slot = var;
4174 VALUE_RECURSED_INTO (node->loc) = true;
4178 dstslot = shared_hash_find_slot_noinsert_1 (dst->vars, dv, dvhash);
4179 gcc_assert (*dstslot == dvar);
4180 canonicalize_values_star (dstslot, dst);
4181 gcc_checking_assert (dstslot
4182 == shared_hash_find_slot_noinsert_1 (dst->vars,
4183 dv, dvhash));
4184 dvar = *dstslot;
4188 if (!onepart_variable_different_p (dvar, s2var))
4190 variable_htab_free (dvar);
4191 *dstslot = dvar = s2var;
4192 dvar->refcount++;
4194 else if (s2var != s1var && !onepart_variable_different_p (dvar, s1var))
4196 variable_htab_free (dvar);
4197 *dstslot = dvar = s1var;
4198 dvar->refcount++;
4199 dst_can_be_shared = false;
4201 else
4202 dst_can_be_shared = false;
4204 return 1;
4207 /* Copy s2slot (in DSM->src) to DSM->dst if the variable is a
4208 multi-part variable. Unions of multi-part variables and
4209 intersections of one-part ones will be handled in
4210 variable_merge_over_cur(). */
4212 static int
4213 variable_merge_over_src (variable *s2var, struct dfset_merge *dsm)
4215 dataflow_set *dst = dsm->dst;
4216 decl_or_value dv = s2var->dv;
4218 if (!s2var->onepart)
4220 variable **dstp = shared_hash_find_slot (dst->vars, dv);
4221 *dstp = s2var;
4222 s2var->refcount++;
4223 return 1;
4226 dsm->src_onepart_cnt++;
4227 return 1;
4230 /* Combine dataflow set information from SRC2 into DST, using PDST
4231 to carry over information across passes. */
4233 static void
4234 dataflow_set_merge (dataflow_set *dst, dataflow_set *src2)
4236 dataflow_set cur = *dst;
4237 dataflow_set *src1 = &cur;
4238 struct dfset_merge dsm;
4239 int i;
4240 size_t src1_elems, src2_elems;
4241 variable_iterator_type hi;
4242 variable *var;
4244 src1_elems = shared_hash_htab (src1->vars)->elements ();
4245 src2_elems = shared_hash_htab (src2->vars)->elements ();
4246 dataflow_set_init (dst);
4247 dst->stack_adjust = cur.stack_adjust;
4248 shared_hash_destroy (dst->vars);
4249 dst->vars = new shared_hash;
4250 dst->vars->refcount = 1;
4251 dst->vars->htab = new variable_table_type (MAX (src1_elems, src2_elems));
4253 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
4254 attrs_list_mpdv_union (&dst->regs[i], src1->regs[i], src2->regs[i]);
4256 dsm.dst = dst;
4257 dsm.src = src2;
4258 dsm.cur = src1;
4259 dsm.src_onepart_cnt = 0;
4261 FOR_EACH_HASH_TABLE_ELEMENT (*shared_hash_htab (dsm.src->vars),
4262 var, variable, hi)
4263 variable_merge_over_src (var, &dsm);
4264 FOR_EACH_HASH_TABLE_ELEMENT (*shared_hash_htab (dsm.cur->vars),
4265 var, variable, hi)
4266 variable_merge_over_cur (var, &dsm);
4268 if (dsm.src_onepart_cnt)
4269 dst_can_be_shared = false;
4271 dataflow_set_destroy (src1);
4274 /* Mark register equivalences. */
4276 static void
4277 dataflow_set_equiv_regs (dataflow_set *set)
4279 int i;
4280 attrs *list, **listp;
4282 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
4284 rtx canon[NUM_MACHINE_MODES];
4286 /* If the list is empty or one entry, no need to canonicalize
4287 anything. */
4288 if (set->regs[i] == NULL || set->regs[i]->next == NULL)
4289 continue;
4291 memset (canon, 0, sizeof (canon));
4293 for (list = set->regs[i]; list; list = list->next)
4294 if (list->offset == 0 && dv_is_value_p (list->dv))
4296 rtx val = dv_as_value (list->dv);
4297 rtx *cvalp = &canon[(int)GET_MODE (val)];
4298 rtx cval = *cvalp;
4300 if (canon_value_cmp (val, cval))
4301 *cvalp = val;
4304 for (list = set->regs[i]; list; list = list->next)
4305 if (list->offset == 0 && dv_onepart_p (list->dv))
4307 rtx cval = canon[(int)GET_MODE (list->loc)];
4309 if (!cval)
4310 continue;
4312 if (dv_is_value_p (list->dv))
4314 rtx val = dv_as_value (list->dv);
4316 if (val == cval)
4317 continue;
4319 VALUE_RECURSED_INTO (val) = true;
4320 set_variable_part (set, val, dv_from_value (cval), 0,
4321 VAR_INIT_STATUS_INITIALIZED,
4322 NULL, NO_INSERT);
4325 VALUE_RECURSED_INTO (cval) = true;
4326 set_variable_part (set, cval, list->dv, 0,
4327 VAR_INIT_STATUS_INITIALIZED, NULL, NO_INSERT);
4330 for (listp = &set->regs[i]; (list = *listp);
4331 listp = list ? &list->next : listp)
4332 if (list->offset == 0 && dv_onepart_p (list->dv))
4334 rtx cval = canon[(int)GET_MODE (list->loc)];
4335 variable **slot;
4337 if (!cval)
4338 continue;
4340 if (dv_is_value_p (list->dv))
4342 rtx val = dv_as_value (list->dv);
4343 if (!VALUE_RECURSED_INTO (val))
4344 continue;
4347 slot = shared_hash_find_slot_noinsert (set->vars, list->dv);
4348 canonicalize_values_star (slot, set);
4349 if (*listp != list)
4350 list = NULL;
4355 /* Remove any redundant values in the location list of VAR, which must
4356 be unshared and 1-part. */
4358 static void
4359 remove_duplicate_values (variable *var)
4361 location_chain *node, **nodep;
4363 gcc_assert (var->onepart);
4364 gcc_assert (var->n_var_parts == 1);
4365 gcc_assert (var->refcount == 1);
4367 for (nodep = &var->var_part[0].loc_chain; (node = *nodep); )
4369 if (GET_CODE (node->loc) == VALUE)
4371 if (VALUE_RECURSED_INTO (node->loc))
4373 /* Remove duplicate value node. */
4374 *nodep = node->next;
4375 delete node;
4376 continue;
4378 else
4379 VALUE_RECURSED_INTO (node->loc) = true;
4381 nodep = &node->next;
4384 for (node = var->var_part[0].loc_chain; node; node = node->next)
4385 if (GET_CODE (node->loc) == VALUE)
4387 gcc_assert (VALUE_RECURSED_INTO (node->loc));
4388 VALUE_RECURSED_INTO (node->loc) = false;
4393 /* Hash table iteration argument passed to variable_post_merge. */
4394 struct dfset_post_merge
4396 /* The new input set for the current block. */
4397 dataflow_set *set;
4398 /* Pointer to the permanent input set for the current block, or
4399 NULL. */
4400 dataflow_set **permp;
4403 /* Create values for incoming expressions associated with one-part
4404 variables that don't have value numbers for them. */
4407 variable_post_merge_new_vals (variable **slot, dfset_post_merge *dfpm)
4409 dataflow_set *set = dfpm->set;
4410 variable *var = *slot;
4411 location_chain *node;
4413 if (!var->onepart || !var->n_var_parts)
4414 return 1;
4416 gcc_assert (var->n_var_parts == 1);
4418 if (dv_is_decl_p (var->dv))
4420 bool check_dupes = false;
4422 restart:
4423 for (node = var->var_part[0].loc_chain; node; node = node->next)
4425 if (GET_CODE (node->loc) == VALUE)
4426 gcc_assert (!VALUE_RECURSED_INTO (node->loc));
4427 else if (GET_CODE (node->loc) == REG)
4429 attrs *att, **attp, **curp = NULL;
4431 if (var->refcount != 1)
4433 slot = unshare_variable (set, slot, var,
4434 VAR_INIT_STATUS_INITIALIZED);
4435 var = *slot;
4436 goto restart;
4439 for (attp = &set->regs[REGNO (node->loc)]; (att = *attp);
4440 attp = &att->next)
4441 if (att->offset == 0
4442 && GET_MODE (att->loc) == GET_MODE (node->loc))
4444 if (dv_is_value_p (att->dv))
4446 rtx cval = dv_as_value (att->dv);
4447 node->loc = cval;
4448 check_dupes = true;
4449 break;
4451 else if (dv_as_opaque (att->dv) == dv_as_opaque (var->dv))
4452 curp = attp;
4455 if (!curp)
4457 curp = attp;
4458 while (*curp)
4459 if ((*curp)->offset == 0
4460 && GET_MODE ((*curp)->loc) == GET_MODE (node->loc)
4461 && dv_as_opaque ((*curp)->dv) == dv_as_opaque (var->dv))
4462 break;
4463 else
4464 curp = &(*curp)->next;
4465 gcc_assert (*curp);
4468 if (!att)
4470 decl_or_value cdv;
4471 rtx cval;
4473 if (!*dfpm->permp)
4475 *dfpm->permp = XNEW (dataflow_set);
4476 dataflow_set_init (*dfpm->permp);
4479 for (att = (*dfpm->permp)->regs[REGNO (node->loc)];
4480 att; att = att->next)
4481 if (GET_MODE (att->loc) == GET_MODE (node->loc))
4483 gcc_assert (att->offset == 0
4484 && dv_is_value_p (att->dv));
4485 val_reset (set, att->dv);
4486 break;
4489 if (att)
4491 cdv = att->dv;
4492 cval = dv_as_value (cdv);
4494 else
4496 /* Create a unique value to hold this register,
4497 that ought to be found and reused in
4498 subsequent rounds. */
4499 cselib_val *v;
4500 gcc_assert (!cselib_lookup (node->loc,
4501 GET_MODE (node->loc), 0,
4502 VOIDmode));
4503 v = cselib_lookup (node->loc, GET_MODE (node->loc), 1,
4504 VOIDmode);
4505 cselib_preserve_value (v);
4506 cselib_invalidate_rtx (node->loc);
4507 cval = v->val_rtx;
4508 cdv = dv_from_value (cval);
4509 if (dump_file)
4510 fprintf (dump_file,
4511 "Created new value %u:%u for reg %i\n",
4512 v->uid, v->hash, REGNO (node->loc));
4515 var_reg_decl_set (*dfpm->permp, node->loc,
4516 VAR_INIT_STATUS_INITIALIZED,
4517 cdv, 0, NULL, INSERT);
4519 node->loc = cval;
4520 check_dupes = true;
4523 /* Remove attribute referring to the decl, which now
4524 uses the value for the register, already existing or
4525 to be added when we bring perm in. */
4526 att = *curp;
4527 *curp = att->next;
4528 delete att;
4532 if (check_dupes)
4533 remove_duplicate_values (var);
4536 return 1;
4539 /* Reset values in the permanent set that are not associated with the
4540 chosen expression. */
4543 variable_post_merge_perm_vals (variable **pslot, dfset_post_merge *dfpm)
4545 dataflow_set *set = dfpm->set;
4546 variable *pvar = *pslot, *var;
4547 location_chain *pnode;
4548 decl_or_value dv;
4549 attrs *att;
4551 gcc_assert (dv_is_value_p (pvar->dv)
4552 && pvar->n_var_parts == 1);
4553 pnode = pvar->var_part[0].loc_chain;
4554 gcc_assert (pnode
4555 && !pnode->next
4556 && REG_P (pnode->loc));
4558 dv = pvar->dv;
4560 var = shared_hash_find (set->vars, dv);
4561 if (var)
4563 /* Although variable_post_merge_new_vals may have made decls
4564 non-star-canonical, values that pre-existed in canonical form
4565 remain canonical, and newly-created values reference a single
4566 REG, so they are canonical as well. Since VAR has the
4567 location list for a VALUE, using find_loc_in_1pdv for it is
4568 fine, since VALUEs don't map back to DECLs. */
4569 if (find_loc_in_1pdv (pnode->loc, var, shared_hash_htab (set->vars)))
4570 return 1;
4571 val_reset (set, dv);
4574 for (att = set->regs[REGNO (pnode->loc)]; att; att = att->next)
4575 if (att->offset == 0
4576 && GET_MODE (att->loc) == GET_MODE (pnode->loc)
4577 && dv_is_value_p (att->dv))
4578 break;
4580 /* If there is a value associated with this register already, create
4581 an equivalence. */
4582 if (att && dv_as_value (att->dv) != dv_as_value (dv))
4584 rtx cval = dv_as_value (att->dv);
4585 set_variable_part (set, cval, dv, 0, pnode->init, NULL, INSERT);
4586 set_variable_part (set, dv_as_value (dv), att->dv, 0, pnode->init,
4587 NULL, INSERT);
4589 else if (!att)
4591 attrs_list_insert (&set->regs[REGNO (pnode->loc)],
4592 dv, 0, pnode->loc);
4593 variable_union (pvar, set);
4596 return 1;
4599 /* Just checking stuff and registering register attributes for
4600 now. */
4602 static void
4603 dataflow_post_merge_adjust (dataflow_set *set, dataflow_set **permp)
4605 struct dfset_post_merge dfpm;
4607 dfpm.set = set;
4608 dfpm.permp = permp;
4610 shared_hash_htab (set->vars)
4611 ->traverse <dfset_post_merge*, variable_post_merge_new_vals> (&dfpm);
4612 if (*permp)
4613 shared_hash_htab ((*permp)->vars)
4614 ->traverse <dfset_post_merge*, variable_post_merge_perm_vals> (&dfpm);
4615 shared_hash_htab (set->vars)
4616 ->traverse <dataflow_set *, canonicalize_values_star> (set);
4617 shared_hash_htab (set->vars)
4618 ->traverse <dataflow_set *, canonicalize_vars_star> (set);
4621 /* Return a node whose loc is a MEM that refers to EXPR in the
4622 location list of a one-part variable or value VAR, or in that of
4623 any values recursively mentioned in the location lists. */
4625 static location_chain *
4626 find_mem_expr_in_1pdv (tree expr, rtx val, variable_table_type *vars)
4628 location_chain *node;
4629 decl_or_value dv;
4630 variable *var;
4631 location_chain *where = NULL;
4633 if (!val)
4634 return NULL;
4636 gcc_assert (GET_CODE (val) == VALUE
4637 && !VALUE_RECURSED_INTO (val));
4639 dv = dv_from_value (val);
4640 var = vars->find_with_hash (dv, dv_htab_hash (dv));
4642 if (!var)
4643 return NULL;
4645 gcc_assert (var->onepart);
4647 if (!var->n_var_parts)
4648 return NULL;
4650 VALUE_RECURSED_INTO (val) = true;
4652 for (node = var->var_part[0].loc_chain; node; node = node->next)
4653 if (MEM_P (node->loc)
4654 && MEM_EXPR (node->loc) == expr
4655 && int_mem_offset (node->loc) == 0)
4657 where = node;
4658 break;
4660 else if (GET_CODE (node->loc) == VALUE
4661 && !VALUE_RECURSED_INTO (node->loc)
4662 && (where = find_mem_expr_in_1pdv (expr, node->loc, vars)))
4663 break;
4665 VALUE_RECURSED_INTO (val) = false;
4667 return where;
4670 /* Return TRUE if the value of MEM may vary across a call. */
4672 static bool
4673 mem_dies_at_call (rtx mem)
4675 tree expr = MEM_EXPR (mem);
4676 tree decl;
4678 if (!expr)
4679 return true;
4681 decl = get_base_address (expr);
4683 if (!decl)
4684 return true;
4686 if (!DECL_P (decl))
4687 return true;
4689 return (may_be_aliased (decl)
4690 || (!TREE_READONLY (decl) && is_global_var (decl)));
4693 /* Remove all MEMs from the location list of a hash table entry for a
4694 one-part variable, except those whose MEM attributes map back to
4695 the variable itself, directly or within a VALUE. */
4698 dataflow_set_preserve_mem_locs (variable **slot, dataflow_set *set)
4700 variable *var = *slot;
4702 if (var->onepart == ONEPART_VDECL || var->onepart == ONEPART_DEXPR)
4704 tree decl = dv_as_decl (var->dv);
4705 location_chain *loc, **locp;
4706 bool changed = false;
4708 if (!var->n_var_parts)
4709 return 1;
4711 gcc_assert (var->n_var_parts == 1);
4713 if (shared_var_p (var, set->vars))
4715 for (loc = var->var_part[0].loc_chain; loc; loc = loc->next)
4717 /* We want to remove dying MEMs that don't refer to DECL. */
4718 if (GET_CODE (loc->loc) == MEM
4719 && (MEM_EXPR (loc->loc) != decl
4720 || int_mem_offset (loc->loc) != 0)
4721 && mem_dies_at_call (loc->loc))
4722 break;
4723 /* We want to move here MEMs that do refer to DECL. */
4724 else if (GET_CODE (loc->loc) == VALUE
4725 && find_mem_expr_in_1pdv (decl, loc->loc,
4726 shared_hash_htab (set->vars)))
4727 break;
4730 if (!loc)
4731 return 1;
4733 slot = unshare_variable (set, slot, var, VAR_INIT_STATUS_UNKNOWN);
4734 var = *slot;
4735 gcc_assert (var->n_var_parts == 1);
4738 for (locp = &var->var_part[0].loc_chain, loc = *locp;
4739 loc; loc = *locp)
4741 rtx old_loc = loc->loc;
4742 if (GET_CODE (old_loc) == VALUE)
4744 location_chain *mem_node
4745 = find_mem_expr_in_1pdv (decl, loc->loc,
4746 shared_hash_htab (set->vars));
4748 /* ??? This picks up only one out of multiple MEMs that
4749 refer to the same variable. Do we ever need to be
4750 concerned about dealing with more than one, or, given
4751 that they should all map to the same variable
4752 location, their addresses will have been merged and
4753 they will be regarded as equivalent? */
4754 if (mem_node)
4756 loc->loc = mem_node->loc;
4757 loc->set_src = mem_node->set_src;
4758 loc->init = MIN (loc->init, mem_node->init);
4762 if (GET_CODE (loc->loc) != MEM
4763 || (MEM_EXPR (loc->loc) == decl
4764 && int_mem_offset (loc->loc) == 0)
4765 || !mem_dies_at_call (loc->loc))
4767 if (old_loc != loc->loc && emit_notes)
4769 if (old_loc == var->var_part[0].cur_loc)
4771 changed = true;
4772 var->var_part[0].cur_loc = NULL;
4775 locp = &loc->next;
4776 continue;
4779 if (emit_notes)
4781 if (old_loc == var->var_part[0].cur_loc)
4783 changed = true;
4784 var->var_part[0].cur_loc = NULL;
4787 *locp = loc->next;
4788 delete loc;
4791 if (!var->var_part[0].loc_chain)
4793 var->n_var_parts--;
4794 changed = true;
4796 if (changed)
4797 variable_was_changed (var, set);
4800 return 1;
4803 /* Remove all MEMs from the location list of a hash table entry for a
4804 onepart variable. */
4807 dataflow_set_remove_mem_locs (variable **slot, dataflow_set *set)
4809 variable *var = *slot;
4811 if (var->onepart != NOT_ONEPART)
4813 location_chain *loc, **locp;
4814 bool changed = false;
4815 rtx cur_loc;
4817 gcc_assert (var->n_var_parts == 1);
4819 if (shared_var_p (var, set->vars))
4821 for (loc = var->var_part[0].loc_chain; loc; loc = loc->next)
4822 if (GET_CODE (loc->loc) == MEM
4823 && mem_dies_at_call (loc->loc))
4824 break;
4826 if (!loc)
4827 return 1;
4829 slot = unshare_variable (set, slot, var, VAR_INIT_STATUS_UNKNOWN);
4830 var = *slot;
4831 gcc_assert (var->n_var_parts == 1);
4834 if (VAR_LOC_1PAUX (var))
4835 cur_loc = VAR_LOC_FROM (var);
4836 else
4837 cur_loc = var->var_part[0].cur_loc;
4839 for (locp = &var->var_part[0].loc_chain, loc = *locp;
4840 loc; loc = *locp)
4842 if (GET_CODE (loc->loc) != MEM
4843 || !mem_dies_at_call (loc->loc))
4845 locp = &loc->next;
4846 continue;
4849 *locp = loc->next;
4850 /* If we have deleted the location which was last emitted
4851 we have to emit new location so add the variable to set
4852 of changed variables. */
4853 if (cur_loc == loc->loc)
4855 changed = true;
4856 var->var_part[0].cur_loc = NULL;
4857 if (VAR_LOC_1PAUX (var))
4858 VAR_LOC_FROM (var) = NULL;
4860 delete loc;
4863 if (!var->var_part[0].loc_chain)
4865 var->n_var_parts--;
4866 changed = true;
4868 if (changed)
4869 variable_was_changed (var, set);
4872 return 1;
4875 /* Remove all variable-location information about call-clobbered
4876 registers, as well as associations between MEMs and VALUEs. */
4878 static void
4879 dataflow_set_clear_at_call (dataflow_set *set, rtx_insn *call_insn)
4881 unsigned int r;
4882 hard_reg_set_iterator hrsi;
4883 HARD_REG_SET invalidated_regs;
4885 get_call_reg_set_usage (call_insn, &invalidated_regs,
4886 regs_invalidated_by_call);
4888 EXECUTE_IF_SET_IN_HARD_REG_SET (invalidated_regs, 0, r, hrsi)
4889 var_regno_delete (set, r);
4891 if (MAY_HAVE_DEBUG_BIND_INSNS)
4893 set->traversed_vars = set->vars;
4894 shared_hash_htab (set->vars)
4895 ->traverse <dataflow_set *, dataflow_set_preserve_mem_locs> (set);
4896 set->traversed_vars = set->vars;
4897 shared_hash_htab (set->vars)
4898 ->traverse <dataflow_set *, dataflow_set_remove_mem_locs> (set);
4899 set->traversed_vars = NULL;
4903 static bool
4904 variable_part_different_p (variable_part *vp1, variable_part *vp2)
4906 location_chain *lc1, *lc2;
4908 for (lc1 = vp1->loc_chain; lc1; lc1 = lc1->next)
4910 for (lc2 = vp2->loc_chain; lc2; lc2 = lc2->next)
4912 if (REG_P (lc1->loc) && REG_P (lc2->loc))
4914 if (REGNO (lc1->loc) == REGNO (lc2->loc))
4915 break;
4917 if (rtx_equal_p (lc1->loc, lc2->loc))
4918 break;
4920 if (!lc2)
4921 return true;
4923 return false;
4926 /* Return true if one-part variables VAR1 and VAR2 are different.
4927 They must be in canonical order. */
4929 static bool
4930 onepart_variable_different_p (variable *var1, variable *var2)
4932 location_chain *lc1, *lc2;
4934 if (var1 == var2)
4935 return false;
4937 gcc_assert (var1->n_var_parts == 1
4938 && var2->n_var_parts == 1);
4940 lc1 = var1->var_part[0].loc_chain;
4941 lc2 = var2->var_part[0].loc_chain;
4943 gcc_assert (lc1 && lc2);
4945 while (lc1 && lc2)
4947 if (loc_cmp (lc1->loc, lc2->loc))
4948 return true;
4949 lc1 = lc1->next;
4950 lc2 = lc2->next;
4953 return lc1 != lc2;
4956 /* Return true if one-part variables VAR1 and VAR2 are different.
4957 They must be in canonical order. */
4959 static void
4960 dump_onepart_variable_differences (variable *var1, variable *var2)
4962 location_chain *lc1, *lc2;
4964 gcc_assert (var1 != var2);
4965 gcc_assert (dump_file);
4966 gcc_assert (dv_as_opaque (var1->dv) == dv_as_opaque (var2->dv));
4967 gcc_assert (var1->n_var_parts == 1
4968 && var2->n_var_parts == 1);
4970 lc1 = var1->var_part[0].loc_chain;
4971 lc2 = var2->var_part[0].loc_chain;
4973 gcc_assert (lc1 && lc2);
4975 while (lc1 && lc2)
4977 switch (loc_cmp (lc1->loc, lc2->loc))
4979 case -1:
4980 fprintf (dump_file, "removed: ");
4981 print_rtl_single (dump_file, lc1->loc);
4982 lc1 = lc1->next;
4983 continue;
4984 case 0:
4985 break;
4986 case 1:
4987 fprintf (dump_file, "added: ");
4988 print_rtl_single (dump_file, lc2->loc);
4989 lc2 = lc2->next;
4990 continue;
4991 default:
4992 gcc_unreachable ();
4994 lc1 = lc1->next;
4995 lc2 = lc2->next;
4998 while (lc1)
5000 fprintf (dump_file, "removed: ");
5001 print_rtl_single (dump_file, lc1->loc);
5002 lc1 = lc1->next;
5005 while (lc2)
5007 fprintf (dump_file, "added: ");
5008 print_rtl_single (dump_file, lc2->loc);
5009 lc2 = lc2->next;
5013 /* Return true if variables VAR1 and VAR2 are different. */
5015 static bool
5016 variable_different_p (variable *var1, variable *var2)
5018 int i;
5020 if (var1 == var2)
5021 return false;
5023 if (var1->onepart != var2->onepart)
5024 return true;
5026 if (var1->n_var_parts != var2->n_var_parts)
5027 return true;
5029 if (var1->onepart && var1->n_var_parts)
5031 gcc_checking_assert (dv_as_opaque (var1->dv) == dv_as_opaque (var2->dv)
5032 && var1->n_var_parts == 1);
5033 /* One-part values have locations in a canonical order. */
5034 return onepart_variable_different_p (var1, var2);
5037 for (i = 0; i < var1->n_var_parts; i++)
5039 if (VAR_PART_OFFSET (var1, i) != VAR_PART_OFFSET (var2, i))
5040 return true;
5041 if (variable_part_different_p (&var1->var_part[i], &var2->var_part[i]))
5042 return true;
5043 if (variable_part_different_p (&var2->var_part[i], &var1->var_part[i]))
5044 return true;
5046 return false;
5049 /* Return true if dataflow sets OLD_SET and NEW_SET differ. */
5051 static bool
5052 dataflow_set_different (dataflow_set *old_set, dataflow_set *new_set)
5054 variable_iterator_type hi;
5055 variable *var1;
5056 bool diffound = false;
5057 bool details = (dump_file && (dump_flags & TDF_DETAILS));
5059 #define RETRUE \
5060 do \
5062 if (!details) \
5063 return true; \
5064 else \
5065 diffound = true; \
5067 while (0)
5069 if (old_set->vars == new_set->vars)
5070 return false;
5072 if (shared_hash_htab (old_set->vars)->elements ()
5073 != shared_hash_htab (new_set->vars)->elements ())
5074 RETRUE;
5076 FOR_EACH_HASH_TABLE_ELEMENT (*shared_hash_htab (old_set->vars),
5077 var1, variable, hi)
5079 variable_table_type *htab = shared_hash_htab (new_set->vars);
5080 variable *var2 = htab->find_with_hash (var1->dv, dv_htab_hash (var1->dv));
5082 if (!var2)
5084 if (dump_file && (dump_flags & TDF_DETAILS))
5086 fprintf (dump_file, "dataflow difference found: removal of:\n");
5087 dump_var (var1);
5089 RETRUE;
5091 else if (variable_different_p (var1, var2))
5093 if (details)
5095 fprintf (dump_file, "dataflow difference found: "
5096 "old and new follow:\n");
5097 dump_var (var1);
5098 if (dv_onepart_p (var1->dv))
5099 dump_onepart_variable_differences (var1, var2);
5100 dump_var (var2);
5102 RETRUE;
5106 /* There's no need to traverse the second hashtab unless we want to
5107 print the details. If both have the same number of elements and
5108 the second one had all entries found in the first one, then the
5109 second can't have any extra entries. */
5110 if (!details)
5111 return diffound;
5113 FOR_EACH_HASH_TABLE_ELEMENT (*shared_hash_htab (new_set->vars),
5114 var1, variable, hi)
5116 variable_table_type *htab = shared_hash_htab (old_set->vars);
5117 variable *var2 = htab->find_with_hash (var1->dv, dv_htab_hash (var1->dv));
5118 if (!var2)
5120 if (details)
5122 fprintf (dump_file, "dataflow difference found: addition of:\n");
5123 dump_var (var1);
5125 RETRUE;
5129 #undef RETRUE
5131 return diffound;
5134 /* Free the contents of dataflow set SET. */
5136 static void
5137 dataflow_set_destroy (dataflow_set *set)
5139 int i;
5141 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
5142 attrs_list_clear (&set->regs[i]);
5144 shared_hash_destroy (set->vars);
5145 set->vars = NULL;
5148 /* Return true if T is a tracked parameter with non-degenerate record type. */
5150 static bool
5151 tracked_record_parameter_p (tree t)
5153 if (TREE_CODE (t) != PARM_DECL)
5154 return false;
5156 if (DECL_MODE (t) == BLKmode)
5157 return false;
5159 tree type = TREE_TYPE (t);
5160 if (TREE_CODE (type) != RECORD_TYPE)
5161 return false;
5163 if (TYPE_FIELDS (type) == NULL_TREE
5164 || DECL_CHAIN (TYPE_FIELDS (type)) == NULL_TREE)
5165 return false;
5167 return true;
5170 /* Shall EXPR be tracked? */
5172 static bool
5173 track_expr_p (tree expr, bool need_rtl)
5175 rtx decl_rtl;
5176 tree realdecl;
5178 if (TREE_CODE (expr) == DEBUG_EXPR_DECL)
5179 return DECL_RTL_SET_P (expr);
5181 /* If EXPR is not a parameter or a variable do not track it. */
5182 if (!VAR_P (expr) && TREE_CODE (expr) != PARM_DECL)
5183 return 0;
5185 /* It also must have a name... */
5186 if (!DECL_NAME (expr) && need_rtl)
5187 return 0;
5189 /* ... and a RTL assigned to it. */
5190 decl_rtl = DECL_RTL_IF_SET (expr);
5191 if (!decl_rtl && need_rtl)
5192 return 0;
5194 /* If this expression is really a debug alias of some other declaration, we
5195 don't need to track this expression if the ultimate declaration is
5196 ignored. */
5197 realdecl = expr;
5198 if (VAR_P (realdecl) && DECL_HAS_DEBUG_EXPR_P (realdecl))
5200 realdecl = DECL_DEBUG_EXPR (realdecl);
5201 if (!DECL_P (realdecl))
5203 if (handled_component_p (realdecl)
5204 || (TREE_CODE (realdecl) == MEM_REF
5205 && TREE_CODE (TREE_OPERAND (realdecl, 0)) == ADDR_EXPR))
5207 HOST_WIDE_INT bitsize, bitpos;
5208 bool reverse;
5209 tree innerdecl
5210 = get_ref_base_and_extent_hwi (realdecl, &bitpos,
5211 &bitsize, &reverse);
5212 if (!innerdecl
5213 || !DECL_P (innerdecl)
5214 || DECL_IGNORED_P (innerdecl)
5215 /* Do not track declarations for parts of tracked record
5216 parameters since we want to track them as a whole. */
5217 || tracked_record_parameter_p (innerdecl)
5218 || TREE_STATIC (innerdecl)
5219 || bitsize == 0
5220 || bitpos + bitsize > 256)
5221 return 0;
5222 else
5223 realdecl = expr;
5225 else
5226 return 0;
5230 /* Do not track EXPR if REALDECL it should be ignored for debugging
5231 purposes. */
5232 if (DECL_IGNORED_P (realdecl))
5233 return 0;
5235 /* Do not track global variables until we are able to emit correct location
5236 list for them. */
5237 if (TREE_STATIC (realdecl))
5238 return 0;
5240 /* When the EXPR is a DECL for alias of some variable (see example)
5241 the TREE_STATIC flag is not used. Disable tracking all DECLs whose
5242 DECL_RTL contains SYMBOL_REF.
5244 Example:
5245 extern char **_dl_argv_internal __attribute__ ((alias ("_dl_argv")));
5246 char **_dl_argv;
5248 if (decl_rtl && MEM_P (decl_rtl)
5249 && contains_symbol_ref_p (XEXP (decl_rtl, 0)))
5250 return 0;
5252 /* If RTX is a memory it should not be very large (because it would be
5253 an array or struct). */
5254 if (decl_rtl && MEM_P (decl_rtl))
5256 /* Do not track structures and arrays. */
5257 if ((GET_MODE (decl_rtl) == BLKmode
5258 || AGGREGATE_TYPE_P (TREE_TYPE (realdecl)))
5259 && !tracked_record_parameter_p (realdecl))
5260 return 0;
5261 if (MEM_SIZE_KNOWN_P (decl_rtl)
5262 && maybe_gt (MEM_SIZE (decl_rtl), MAX_VAR_PARTS))
5263 return 0;
5266 DECL_CHANGED (expr) = 0;
5267 DECL_CHANGED (realdecl) = 0;
5268 return 1;
5271 /* Determine whether a given LOC refers to the same variable part as
5272 EXPR+OFFSET. */
5274 static bool
5275 same_variable_part_p (rtx loc, tree expr, poly_int64 offset)
5277 tree expr2;
5278 poly_int64 offset2;
5280 if (! DECL_P (expr))
5281 return false;
5283 if (REG_P (loc))
5285 expr2 = REG_EXPR (loc);
5286 offset2 = REG_OFFSET (loc);
5288 else if (MEM_P (loc))
5290 expr2 = MEM_EXPR (loc);
5291 offset2 = int_mem_offset (loc);
5293 else
5294 return false;
5296 if (! expr2 || ! DECL_P (expr2))
5297 return false;
5299 expr = var_debug_decl (expr);
5300 expr2 = var_debug_decl (expr2);
5302 return (expr == expr2 && known_eq (offset, offset2));
5305 /* LOC is a REG or MEM that we would like to track if possible.
5306 If EXPR is null, we don't know what expression LOC refers to,
5307 otherwise it refers to EXPR + OFFSET. STORE_REG_P is true if
5308 LOC is an lvalue register.
5310 Return true if EXPR is nonnull and if LOC, or some lowpart of it,
5311 is something we can track. When returning true, store the mode of
5312 the lowpart we can track in *MODE_OUT (if nonnull) and its offset
5313 from EXPR in *OFFSET_OUT (if nonnull). */
5315 static bool
5316 track_loc_p (rtx loc, tree expr, poly_int64 offset, bool store_reg_p,
5317 machine_mode *mode_out, HOST_WIDE_INT *offset_out)
5319 machine_mode mode;
5321 if (expr == NULL || !track_expr_p (expr, true))
5322 return false;
5324 /* If REG was a paradoxical subreg, its REG_ATTRS will describe the
5325 whole subreg, but only the old inner part is really relevant. */
5326 mode = GET_MODE (loc);
5327 if (REG_P (loc) && !HARD_REGISTER_NUM_P (ORIGINAL_REGNO (loc)))
5329 machine_mode pseudo_mode;
5331 pseudo_mode = PSEUDO_REGNO_MODE (ORIGINAL_REGNO (loc));
5332 if (paradoxical_subreg_p (mode, pseudo_mode))
5334 offset += byte_lowpart_offset (pseudo_mode, mode);
5335 mode = pseudo_mode;
5339 /* If LOC is a paradoxical lowpart of EXPR, refer to EXPR itself.
5340 Do the same if we are storing to a register and EXPR occupies
5341 the whole of register LOC; in that case, the whole of EXPR is
5342 being changed. We exclude complex modes from the second case
5343 because the real and imaginary parts are represented as separate
5344 pseudo registers, even if the whole complex value fits into one
5345 hard register. */
5346 if ((paradoxical_subreg_p (mode, DECL_MODE (expr))
5347 || (store_reg_p
5348 && !COMPLEX_MODE_P (DECL_MODE (expr))
5349 && hard_regno_nregs (REGNO (loc), DECL_MODE (expr)) == 1))
5350 && known_eq (offset + byte_lowpart_offset (DECL_MODE (expr), mode), 0))
5352 mode = DECL_MODE (expr);
5353 offset = 0;
5356 HOST_WIDE_INT const_offset;
5357 if (!track_offset_p (offset, &const_offset))
5358 return false;
5360 if (mode_out)
5361 *mode_out = mode;
5362 if (offset_out)
5363 *offset_out = const_offset;
5364 return true;
5367 /* Return the MODE lowpart of LOC, or null if LOC is not something we
5368 want to track. When returning nonnull, make sure that the attributes
5369 on the returned value are updated. */
5371 static rtx
5372 var_lowpart (machine_mode mode, rtx loc)
5374 unsigned int regno;
5376 if (GET_MODE (loc) == mode)
5377 return loc;
5379 if (!REG_P (loc) && !MEM_P (loc))
5380 return NULL;
5382 poly_uint64 offset = byte_lowpart_offset (mode, GET_MODE (loc));
5384 if (MEM_P (loc))
5385 return adjust_address_nv (loc, mode, offset);
5387 poly_uint64 reg_offset = subreg_lowpart_offset (mode, GET_MODE (loc));
5388 regno = REGNO (loc) + subreg_regno_offset (REGNO (loc), GET_MODE (loc),
5389 reg_offset, mode);
5390 return gen_rtx_REG_offset (loc, mode, regno, offset);
5393 /* Carry information about uses and stores while walking rtx. */
5395 struct count_use_info
5397 /* The insn where the RTX is. */
5398 rtx_insn *insn;
5400 /* The basic block where insn is. */
5401 basic_block bb;
5403 /* The array of n_sets sets in the insn, as determined by cselib. */
5404 struct cselib_set *sets;
5405 int n_sets;
5407 /* True if we're counting stores, false otherwise. */
5408 bool store_p;
5411 /* Find a VALUE corresponding to X. */
5413 static inline cselib_val *
5414 find_use_val (rtx x, machine_mode mode, struct count_use_info *cui)
5416 int i;
5418 if (cui->sets)
5420 /* This is called after uses are set up and before stores are
5421 processed by cselib, so it's safe to look up srcs, but not
5422 dsts. So we look up expressions that appear in srcs or in
5423 dest expressions, but we search the sets array for dests of
5424 stores. */
5425 if (cui->store_p)
5427 /* Some targets represent memset and memcpy patterns
5428 by (set (mem:BLK ...) (reg:[QHSD]I ...)) or
5429 (set (mem:BLK ...) (const_int ...)) or
5430 (set (mem:BLK ...) (mem:BLK ...)). Don't return anything
5431 in that case, otherwise we end up with mode mismatches. */
5432 if (mode == BLKmode && MEM_P (x))
5433 return NULL;
5434 for (i = 0; i < cui->n_sets; i++)
5435 if (cui->sets[i].dest == x)
5436 return cui->sets[i].src_elt;
5438 else
5439 return cselib_lookup (x, mode, 0, VOIDmode);
5442 return NULL;
5445 /* Replace all registers and addresses in an expression with VALUE
5446 expressions that map back to them, unless the expression is a
5447 register. If no mapping is or can be performed, returns NULL. */
5449 static rtx
5450 replace_expr_with_values (rtx loc)
5452 if (REG_P (loc) || GET_CODE (loc) == ENTRY_VALUE)
5453 return NULL;
5454 else if (MEM_P (loc))
5456 cselib_val *addr = cselib_lookup (XEXP (loc, 0),
5457 get_address_mode (loc), 0,
5458 GET_MODE (loc));
5459 if (addr)
5460 return replace_equiv_address_nv (loc, addr->val_rtx);
5461 else
5462 return NULL;
5464 else
5465 return cselib_subst_to_values (loc, VOIDmode);
5468 /* Return true if X contains a DEBUG_EXPR. */
5470 static bool
5471 rtx_debug_expr_p (const_rtx x)
5473 subrtx_iterator::array_type array;
5474 FOR_EACH_SUBRTX (iter, array, x, ALL)
5475 if (GET_CODE (*iter) == DEBUG_EXPR)
5476 return true;
5477 return false;
5480 /* Determine what kind of micro operation to choose for a USE. Return
5481 MO_CLOBBER if no micro operation is to be generated. */
5483 static enum micro_operation_type
5484 use_type (rtx loc, struct count_use_info *cui, machine_mode *modep)
5486 tree expr;
5488 if (cui && cui->sets)
5490 if (GET_CODE (loc) == VAR_LOCATION)
5492 if (track_expr_p (PAT_VAR_LOCATION_DECL (loc), false))
5494 rtx ploc = PAT_VAR_LOCATION_LOC (loc);
5495 if (! VAR_LOC_UNKNOWN_P (ploc))
5497 cselib_val *val = cselib_lookup (ploc, GET_MODE (loc), 1,
5498 VOIDmode);
5500 /* ??? flag_float_store and volatile mems are never
5501 given values, but we could in theory use them for
5502 locations. */
5503 gcc_assert (val || 1);
5505 return MO_VAL_LOC;
5507 else
5508 return MO_CLOBBER;
5511 if (REG_P (loc) || MEM_P (loc))
5513 if (modep)
5514 *modep = GET_MODE (loc);
5515 if (cui->store_p)
5517 if (REG_P (loc)
5518 || (find_use_val (loc, GET_MODE (loc), cui)
5519 && cselib_lookup (XEXP (loc, 0),
5520 get_address_mode (loc), 0,
5521 GET_MODE (loc))))
5522 return MO_VAL_SET;
5524 else
5526 cselib_val *val = find_use_val (loc, GET_MODE (loc), cui);
5528 if (val && !cselib_preserved_value_p (val))
5529 return MO_VAL_USE;
5534 if (REG_P (loc))
5536 gcc_assert (REGNO (loc) < FIRST_PSEUDO_REGISTER);
5538 if (loc == cfa_base_rtx)
5539 return MO_CLOBBER;
5540 expr = REG_EXPR (loc);
5542 if (!expr)
5543 return MO_USE_NO_VAR;
5544 else if (target_for_debug_bind (var_debug_decl (expr)))
5545 return MO_CLOBBER;
5546 else if (track_loc_p (loc, expr, REG_OFFSET (loc),
5547 false, modep, NULL))
5548 return MO_USE;
5549 else
5550 return MO_USE_NO_VAR;
5552 else if (MEM_P (loc))
5554 expr = MEM_EXPR (loc);
5556 if (!expr)
5557 return MO_CLOBBER;
5558 else if (target_for_debug_bind (var_debug_decl (expr)))
5559 return MO_CLOBBER;
5560 else if (track_loc_p (loc, expr, int_mem_offset (loc),
5561 false, modep, NULL)
5562 /* Multi-part variables shouldn't refer to one-part
5563 variable names such as VALUEs (never happens) or
5564 DEBUG_EXPRs (only happens in the presence of debug
5565 insns). */
5566 && (!MAY_HAVE_DEBUG_BIND_INSNS
5567 || !rtx_debug_expr_p (XEXP (loc, 0))))
5568 return MO_USE;
5569 else
5570 return MO_CLOBBER;
5573 return MO_CLOBBER;
5576 /* Log to OUT information about micro-operation MOPT involving X in
5577 INSN of BB. */
5579 static inline void
5580 log_op_type (rtx x, basic_block bb, rtx_insn *insn,
5581 enum micro_operation_type mopt, FILE *out)
5583 fprintf (out, "bb %i op %i insn %i %s ",
5584 bb->index, VTI (bb)->mos.length (),
5585 INSN_UID (insn), micro_operation_type_name[mopt]);
5586 print_inline_rtx (out, x, 2);
5587 fputc ('\n', out);
5590 /* Tell whether the CONCAT used to holds a VALUE and its location
5591 needs value resolution, i.e., an attempt of mapping the location
5592 back to other incoming values. */
5593 #define VAL_NEEDS_RESOLUTION(x) \
5594 (RTL_FLAG_CHECK1 ("VAL_NEEDS_RESOLUTION", (x), CONCAT)->volatil)
5595 /* Whether the location in the CONCAT is a tracked expression, that
5596 should also be handled like a MO_USE. */
5597 #define VAL_HOLDS_TRACK_EXPR(x) \
5598 (RTL_FLAG_CHECK1 ("VAL_HOLDS_TRACK_EXPR", (x), CONCAT)->used)
5599 /* Whether the location in the CONCAT should be handled like a MO_COPY
5600 as well. */
5601 #define VAL_EXPR_IS_COPIED(x) \
5602 (RTL_FLAG_CHECK1 ("VAL_EXPR_IS_COPIED", (x), CONCAT)->jump)
5603 /* Whether the location in the CONCAT should be handled like a
5604 MO_CLOBBER as well. */
5605 #define VAL_EXPR_IS_CLOBBERED(x) \
5606 (RTL_FLAG_CHECK1 ("VAL_EXPR_IS_CLOBBERED", (x), CONCAT)->unchanging)
5608 /* All preserved VALUEs. */
5609 static vec<rtx> preserved_values;
5611 /* Ensure VAL is preserved and remember it in a vector for vt_emit_notes. */
5613 static void
5614 preserve_value (cselib_val *val)
5616 cselib_preserve_value (val);
5617 preserved_values.safe_push (val->val_rtx);
5620 /* Helper function for MO_VAL_LOC handling. Return non-zero if
5621 any rtxes not suitable for CONST use not replaced by VALUEs
5622 are discovered. */
5624 static bool
5625 non_suitable_const (const_rtx x)
5627 subrtx_iterator::array_type array;
5628 FOR_EACH_SUBRTX (iter, array, x, ALL)
5630 const_rtx x = *iter;
5631 switch (GET_CODE (x))
5633 case REG:
5634 case DEBUG_EXPR:
5635 case PC:
5636 case SCRATCH:
5637 case CC0:
5638 case ASM_INPUT:
5639 case ASM_OPERANDS:
5640 return true;
5641 case MEM:
5642 if (!MEM_READONLY_P (x))
5643 return true;
5644 break;
5645 default:
5646 break;
5649 return false;
5652 /* Add uses (register and memory references) LOC which will be tracked
5653 to VTI (bb)->mos. */
5655 static void
5656 add_uses (rtx loc, struct count_use_info *cui)
5658 machine_mode mode = VOIDmode;
5659 enum micro_operation_type type = use_type (loc, cui, &mode);
5661 if (type != MO_CLOBBER)
5663 basic_block bb = cui->bb;
5664 micro_operation mo;
5666 mo.type = type;
5667 mo.u.loc = type == MO_USE ? var_lowpart (mode, loc) : loc;
5668 mo.insn = cui->insn;
5670 if (type == MO_VAL_LOC)
5672 rtx oloc = loc;
5673 rtx vloc = PAT_VAR_LOCATION_LOC (oloc);
5674 cselib_val *val;
5676 gcc_assert (cui->sets);
5678 if (MEM_P (vloc)
5679 && !REG_P (XEXP (vloc, 0))
5680 && !MEM_P (XEXP (vloc, 0)))
5682 rtx mloc = vloc;
5683 machine_mode address_mode = get_address_mode (mloc);
5684 cselib_val *val
5685 = cselib_lookup (XEXP (mloc, 0), address_mode, 0,
5686 GET_MODE (mloc));
5688 if (val && !cselib_preserved_value_p (val))
5689 preserve_value (val);
5692 if (CONSTANT_P (vloc)
5693 && (GET_CODE (vloc) != CONST || non_suitable_const (vloc)))
5694 /* For constants don't look up any value. */;
5695 else if (!VAR_LOC_UNKNOWN_P (vloc) && !unsuitable_loc (vloc)
5696 && (val = find_use_val (vloc, GET_MODE (oloc), cui)))
5698 machine_mode mode2;
5699 enum micro_operation_type type2;
5700 rtx nloc = NULL;
5701 bool resolvable = REG_P (vloc) || MEM_P (vloc);
5703 if (resolvable)
5704 nloc = replace_expr_with_values (vloc);
5706 if (nloc)
5708 oloc = shallow_copy_rtx (oloc);
5709 PAT_VAR_LOCATION_LOC (oloc) = nloc;
5712 oloc = gen_rtx_CONCAT (mode, val->val_rtx, oloc);
5714 type2 = use_type (vloc, 0, &mode2);
5716 gcc_assert (type2 == MO_USE || type2 == MO_USE_NO_VAR
5717 || type2 == MO_CLOBBER);
5719 if (type2 == MO_CLOBBER
5720 && !cselib_preserved_value_p (val))
5722 VAL_NEEDS_RESOLUTION (oloc) = resolvable;
5723 preserve_value (val);
5726 else if (!VAR_LOC_UNKNOWN_P (vloc))
5728 oloc = shallow_copy_rtx (oloc);
5729 PAT_VAR_LOCATION_LOC (oloc) = gen_rtx_UNKNOWN_VAR_LOC ();
5732 mo.u.loc = oloc;
5734 else if (type == MO_VAL_USE)
5736 machine_mode mode2 = VOIDmode;
5737 enum micro_operation_type type2;
5738 cselib_val *val = find_use_val (loc, GET_MODE (loc), cui);
5739 rtx vloc, oloc = loc, nloc;
5741 gcc_assert (cui->sets);
5743 if (MEM_P (oloc)
5744 && !REG_P (XEXP (oloc, 0))
5745 && !MEM_P (XEXP (oloc, 0)))
5747 rtx mloc = oloc;
5748 machine_mode address_mode = get_address_mode (mloc);
5749 cselib_val *val
5750 = cselib_lookup (XEXP (mloc, 0), address_mode, 0,
5751 GET_MODE (mloc));
5753 if (val && !cselib_preserved_value_p (val))
5754 preserve_value (val);
5757 type2 = use_type (loc, 0, &mode2);
5759 gcc_assert (type2 == MO_USE || type2 == MO_USE_NO_VAR
5760 || type2 == MO_CLOBBER);
5762 if (type2 == MO_USE)
5763 vloc = var_lowpart (mode2, loc);
5764 else
5765 vloc = oloc;
5767 /* The loc of a MO_VAL_USE may have two forms:
5769 (concat val src): val is at src, a value-based
5770 representation.
5772 (concat (concat val use) src): same as above, with use as
5773 the MO_USE tracked value, if it differs from src.
5777 gcc_checking_assert (REG_P (loc) || MEM_P (loc));
5778 nloc = replace_expr_with_values (loc);
5779 if (!nloc)
5780 nloc = oloc;
5782 if (vloc != nloc)
5783 oloc = gen_rtx_CONCAT (mode2, val->val_rtx, vloc);
5784 else
5785 oloc = val->val_rtx;
5787 mo.u.loc = gen_rtx_CONCAT (mode, oloc, nloc);
5789 if (type2 == MO_USE)
5790 VAL_HOLDS_TRACK_EXPR (mo.u.loc) = 1;
5791 if (!cselib_preserved_value_p (val))
5793 VAL_NEEDS_RESOLUTION (mo.u.loc) = 1;
5794 preserve_value (val);
5797 else
5798 gcc_assert (type == MO_USE || type == MO_USE_NO_VAR);
5800 if (dump_file && (dump_flags & TDF_DETAILS))
5801 log_op_type (mo.u.loc, cui->bb, cui->insn, mo.type, dump_file);
5802 VTI (bb)->mos.safe_push (mo);
5806 /* Helper function for finding all uses of REG/MEM in X in insn INSN. */
5808 static void
5809 add_uses_1 (rtx *x, void *cui)
5811 subrtx_var_iterator::array_type array;
5812 FOR_EACH_SUBRTX_VAR (iter, array, *x, NONCONST)
5813 add_uses (*iter, (struct count_use_info *) cui);
5816 /* This is the value used during expansion of locations. We want it
5817 to be unbounded, so that variables expanded deep in a recursion
5818 nest are fully evaluated, so that their values are cached
5819 correctly. We avoid recursion cycles through other means, and we
5820 don't unshare RTL, so excess complexity is not a problem. */
5821 #define EXPR_DEPTH (INT_MAX)
5822 /* We use this to keep too-complex expressions from being emitted as
5823 location notes, and then to debug information. Users can trade
5824 compile time for ridiculously complex expressions, although they're
5825 seldom useful, and they may often have to be discarded as not
5826 representable anyway. */
5827 #define EXPR_USE_DEPTH (PARAM_VALUE (PARAM_MAX_VARTRACK_EXPR_DEPTH))
5829 /* Attempt to reverse the EXPR operation in the debug info and record
5830 it in the cselib table. Say for reg1 = reg2 + 6 even when reg2 is
5831 no longer live we can express its value as VAL - 6. */
5833 static void
5834 reverse_op (rtx val, const_rtx expr, rtx_insn *insn)
5836 rtx src, arg, ret;
5837 cselib_val *v;
5838 struct elt_loc_list *l;
5839 enum rtx_code code;
5840 int count;
5842 if (GET_CODE (expr) != SET)
5843 return;
5845 if (!REG_P (SET_DEST (expr)) || GET_MODE (val) != GET_MODE (SET_DEST (expr)))
5846 return;
5848 src = SET_SRC (expr);
5849 switch (GET_CODE (src))
5851 case PLUS:
5852 case MINUS:
5853 case XOR:
5854 case NOT:
5855 case NEG:
5856 if (!REG_P (XEXP (src, 0)))
5857 return;
5858 break;
5859 case SIGN_EXTEND:
5860 case ZERO_EXTEND:
5861 if (!REG_P (XEXP (src, 0)) && !MEM_P (XEXP (src, 0)))
5862 return;
5863 break;
5864 default:
5865 return;
5868 if (!SCALAR_INT_MODE_P (GET_MODE (src)) || XEXP (src, 0) == cfa_base_rtx)
5869 return;
5871 v = cselib_lookup (XEXP (src, 0), GET_MODE (XEXP (src, 0)), 0, VOIDmode);
5872 if (!v || !cselib_preserved_value_p (v))
5873 return;
5875 /* Use canonical V to avoid creating multiple redundant expressions
5876 for different VALUES equivalent to V. */
5877 v = canonical_cselib_val (v);
5879 /* Adding a reverse op isn't useful if V already has an always valid
5880 location. Ignore ENTRY_VALUE, while it is always constant, we should
5881 prefer non-ENTRY_VALUE locations whenever possible. */
5882 for (l = v->locs, count = 0; l; l = l->next, count++)
5883 if (CONSTANT_P (l->loc)
5884 && (GET_CODE (l->loc) != CONST || !references_value_p (l->loc, 0)))
5885 return;
5886 /* Avoid creating too large locs lists. */
5887 else if (count == PARAM_VALUE (PARAM_MAX_VARTRACK_REVERSE_OP_SIZE))
5888 return;
5890 switch (GET_CODE (src))
5892 case NOT:
5893 case NEG:
5894 if (GET_MODE (v->val_rtx) != GET_MODE (val))
5895 return;
5896 ret = gen_rtx_fmt_e (GET_CODE (src), GET_MODE (val), val);
5897 break;
5898 case SIGN_EXTEND:
5899 case ZERO_EXTEND:
5900 ret = gen_lowpart_SUBREG (GET_MODE (v->val_rtx), val);
5901 break;
5902 case XOR:
5903 code = XOR;
5904 goto binary;
5905 case PLUS:
5906 code = MINUS;
5907 goto binary;
5908 case MINUS:
5909 code = PLUS;
5910 goto binary;
5911 binary:
5912 if (GET_MODE (v->val_rtx) != GET_MODE (val))
5913 return;
5914 arg = XEXP (src, 1);
5915 if (!CONST_INT_P (arg) && GET_CODE (arg) != SYMBOL_REF)
5917 arg = cselib_expand_value_rtx (arg, scratch_regs, 5);
5918 if (arg == NULL_RTX)
5919 return;
5920 if (!CONST_INT_P (arg) && GET_CODE (arg) != SYMBOL_REF)
5921 return;
5923 ret = simplify_gen_binary (code, GET_MODE (val), val, arg);
5924 break;
5925 default:
5926 gcc_unreachable ();
5929 cselib_add_permanent_equiv (v, ret, insn);
5932 /* Add stores (register and memory references) LOC which will be tracked
5933 to VTI (bb)->mos. EXPR is the RTL expression containing the store.
5934 CUIP->insn is instruction which the LOC is part of. */
5936 static void
5937 add_stores (rtx loc, const_rtx expr, void *cuip)
5939 machine_mode mode = VOIDmode, mode2;
5940 struct count_use_info *cui = (struct count_use_info *)cuip;
5941 basic_block bb = cui->bb;
5942 micro_operation mo;
5943 rtx oloc = loc, nloc, src = NULL;
5944 enum micro_operation_type type = use_type (loc, cui, &mode);
5945 bool track_p = false;
5946 cselib_val *v;
5947 bool resolve, preserve;
5949 if (type == MO_CLOBBER)
5950 return;
5952 mode2 = mode;
5954 if (REG_P (loc))
5956 gcc_assert (loc != cfa_base_rtx);
5957 if ((GET_CODE (expr) == CLOBBER && type != MO_VAL_SET)
5958 || !(track_p = use_type (loc, NULL, &mode2) == MO_USE)
5959 || GET_CODE (expr) == CLOBBER)
5961 mo.type = MO_CLOBBER;
5962 mo.u.loc = loc;
5963 if (GET_CODE (expr) == SET
5964 && (SET_DEST (expr) == loc
5965 || (GET_CODE (SET_DEST (expr)) == STRICT_LOW_PART
5966 && XEXP (SET_DEST (expr), 0) == loc))
5967 && !unsuitable_loc (SET_SRC (expr))
5968 && find_use_val (loc, mode, cui))
5970 gcc_checking_assert (type == MO_VAL_SET);
5971 mo.u.loc = gen_rtx_SET (loc, SET_SRC (expr));
5974 else
5976 if (GET_CODE (expr) == SET
5977 && SET_DEST (expr) == loc
5978 && GET_CODE (SET_SRC (expr)) != ASM_OPERANDS)
5979 src = var_lowpart (mode2, SET_SRC (expr));
5980 loc = var_lowpart (mode2, loc);
5982 if (src == NULL)
5984 mo.type = MO_SET;
5985 mo.u.loc = loc;
5987 else
5989 rtx xexpr = gen_rtx_SET (loc, src);
5990 if (same_variable_part_p (src, REG_EXPR (loc), REG_OFFSET (loc)))
5992 /* If this is an instruction copying (part of) a parameter
5993 passed by invisible reference to its register location,
5994 pretend it's a SET so that the initial memory location
5995 is discarded, as the parameter register can be reused
5996 for other purposes and we do not track locations based
5997 on generic registers. */
5998 if (MEM_P (src)
5999 && REG_EXPR (loc)
6000 && TREE_CODE (REG_EXPR (loc)) == PARM_DECL
6001 && DECL_MODE (REG_EXPR (loc)) != BLKmode
6002 && MEM_P (DECL_INCOMING_RTL (REG_EXPR (loc)))
6003 && XEXP (DECL_INCOMING_RTL (REG_EXPR (loc)), 0)
6004 != arg_pointer_rtx)
6005 mo.type = MO_SET;
6006 else
6007 mo.type = MO_COPY;
6009 else
6010 mo.type = MO_SET;
6011 mo.u.loc = xexpr;
6014 mo.insn = cui->insn;
6016 else if (MEM_P (loc)
6017 && ((track_p = use_type (loc, NULL, &mode2) == MO_USE)
6018 || cui->sets))
6020 if (MEM_P (loc) && type == MO_VAL_SET
6021 && !REG_P (XEXP (loc, 0))
6022 && !MEM_P (XEXP (loc, 0)))
6024 rtx mloc = loc;
6025 machine_mode address_mode = get_address_mode (mloc);
6026 cselib_val *val = cselib_lookup (XEXP (mloc, 0),
6027 address_mode, 0,
6028 GET_MODE (mloc));
6030 if (val && !cselib_preserved_value_p (val))
6031 preserve_value (val);
6034 if (GET_CODE (expr) == CLOBBER || !track_p)
6036 mo.type = MO_CLOBBER;
6037 mo.u.loc = track_p ? var_lowpart (mode2, loc) : loc;
6039 else
6041 if (GET_CODE (expr) == SET
6042 && SET_DEST (expr) == loc
6043 && GET_CODE (SET_SRC (expr)) != ASM_OPERANDS)
6044 src = var_lowpart (mode2, SET_SRC (expr));
6045 loc = var_lowpart (mode2, loc);
6047 if (src == NULL)
6049 mo.type = MO_SET;
6050 mo.u.loc = loc;
6052 else
6054 rtx xexpr = gen_rtx_SET (loc, src);
6055 if (same_variable_part_p (SET_SRC (xexpr),
6056 MEM_EXPR (loc),
6057 int_mem_offset (loc)))
6058 mo.type = MO_COPY;
6059 else
6060 mo.type = MO_SET;
6061 mo.u.loc = xexpr;
6064 mo.insn = cui->insn;
6066 else
6067 return;
6069 if (type != MO_VAL_SET)
6070 goto log_and_return;
6072 v = find_use_val (oloc, mode, cui);
6074 if (!v)
6075 goto log_and_return;
6077 resolve = preserve = !cselib_preserved_value_p (v);
6079 /* We cannot track values for multiple-part variables, so we track only
6080 locations for tracked record parameters. */
6081 if (track_p
6082 && REG_P (loc)
6083 && REG_EXPR (loc)
6084 && tracked_record_parameter_p (REG_EXPR (loc)))
6086 /* Although we don't use the value here, it could be used later by the
6087 mere virtue of its existence as the operand of the reverse operation
6088 that gave rise to it (typically extension/truncation). Make sure it
6089 is preserved as required by vt_expand_var_loc_chain. */
6090 if (preserve)
6091 preserve_value (v);
6092 goto log_and_return;
6095 if (loc == stack_pointer_rtx
6096 && maybe_ne (hard_frame_pointer_adjustment, -1)
6097 && preserve)
6098 cselib_set_value_sp_based (v);
6100 nloc = replace_expr_with_values (oloc);
6101 if (nloc)
6102 oloc = nloc;
6104 if (GET_CODE (PATTERN (cui->insn)) == COND_EXEC)
6106 cselib_val *oval = cselib_lookup (oloc, GET_MODE (oloc), 0, VOIDmode);
6108 if (oval == v)
6109 return;
6110 gcc_assert (REG_P (oloc) || MEM_P (oloc));
6112 if (oval && !cselib_preserved_value_p (oval))
6114 micro_operation moa;
6116 preserve_value (oval);
6118 moa.type = MO_VAL_USE;
6119 moa.u.loc = gen_rtx_CONCAT (mode, oval->val_rtx, oloc);
6120 VAL_NEEDS_RESOLUTION (moa.u.loc) = 1;
6121 moa.insn = cui->insn;
6123 if (dump_file && (dump_flags & TDF_DETAILS))
6124 log_op_type (moa.u.loc, cui->bb, cui->insn,
6125 moa.type, dump_file);
6126 VTI (bb)->mos.safe_push (moa);
6129 resolve = false;
6131 else if (resolve && GET_CODE (mo.u.loc) == SET)
6133 if (REG_P (SET_SRC (expr)) || MEM_P (SET_SRC (expr)))
6134 nloc = replace_expr_with_values (SET_SRC (expr));
6135 else
6136 nloc = NULL_RTX;
6138 /* Avoid the mode mismatch between oexpr and expr. */
6139 if (!nloc && mode != mode2)
6141 nloc = SET_SRC (expr);
6142 gcc_assert (oloc == SET_DEST (expr));
6145 if (nloc && nloc != SET_SRC (mo.u.loc))
6146 oloc = gen_rtx_SET (oloc, nloc);
6147 else
6149 if (oloc == SET_DEST (mo.u.loc))
6150 /* No point in duplicating. */
6151 oloc = mo.u.loc;
6152 if (!REG_P (SET_SRC (mo.u.loc)))
6153 resolve = false;
6156 else if (!resolve)
6158 if (GET_CODE (mo.u.loc) == SET
6159 && oloc == SET_DEST (mo.u.loc))
6160 /* No point in duplicating. */
6161 oloc = mo.u.loc;
6163 else
6164 resolve = false;
6166 loc = gen_rtx_CONCAT (mode, v->val_rtx, oloc);
6168 if (mo.u.loc != oloc)
6169 loc = gen_rtx_CONCAT (GET_MODE (mo.u.loc), loc, mo.u.loc);
6171 /* The loc of a MO_VAL_SET may have various forms:
6173 (concat val dst): dst now holds val
6175 (concat val (set dst src)): dst now holds val, copied from src
6177 (concat (concat val dstv) dst): dst now holds val; dstv is dst
6178 after replacing mems and non-top-level regs with values.
6180 (concat (concat val dstv) (set dst src)): dst now holds val,
6181 copied from src. dstv is a value-based representation of dst, if
6182 it differs from dst. If resolution is needed, src is a REG, and
6183 its mode is the same as that of val.
6185 (concat (concat val (set dstv srcv)) (set dst src)): src
6186 copied to dst, holding val. dstv and srcv are value-based
6187 representations of dst and src, respectively.
6191 if (GET_CODE (PATTERN (cui->insn)) != COND_EXEC)
6192 reverse_op (v->val_rtx, expr, cui->insn);
6194 mo.u.loc = loc;
6196 if (track_p)
6197 VAL_HOLDS_TRACK_EXPR (loc) = 1;
6198 if (preserve)
6200 VAL_NEEDS_RESOLUTION (loc) = resolve;
6201 preserve_value (v);
6203 if (mo.type == MO_CLOBBER)
6204 VAL_EXPR_IS_CLOBBERED (loc) = 1;
6205 if (mo.type == MO_COPY)
6206 VAL_EXPR_IS_COPIED (loc) = 1;
6208 mo.type = MO_VAL_SET;
6210 log_and_return:
6211 if (dump_file && (dump_flags & TDF_DETAILS))
6212 log_op_type (mo.u.loc, cui->bb, cui->insn, mo.type, dump_file);
6213 VTI (bb)->mos.safe_push (mo);
6216 /* Arguments to the call. */
6217 static rtx call_arguments;
6219 /* Compute call_arguments. */
6221 static void
6222 prepare_call_arguments (basic_block bb, rtx_insn *insn)
6224 rtx link, x, call;
6225 rtx prev, cur, next;
6226 rtx this_arg = NULL_RTX;
6227 tree type = NULL_TREE, t, fndecl = NULL_TREE;
6228 tree obj_type_ref = NULL_TREE;
6229 CUMULATIVE_ARGS args_so_far_v;
6230 cumulative_args_t args_so_far;
6232 memset (&args_so_far_v, 0, sizeof (args_so_far_v));
6233 args_so_far = pack_cumulative_args (&args_so_far_v);
6234 call = get_call_rtx_from (insn);
6235 if (call)
6237 if (GET_CODE (XEXP (XEXP (call, 0), 0)) == SYMBOL_REF)
6239 rtx symbol = XEXP (XEXP (call, 0), 0);
6240 if (SYMBOL_REF_DECL (symbol))
6241 fndecl = SYMBOL_REF_DECL (symbol);
6243 if (fndecl == NULL_TREE)
6244 fndecl = MEM_EXPR (XEXP (call, 0));
6245 if (fndecl
6246 && TREE_CODE (TREE_TYPE (fndecl)) != FUNCTION_TYPE
6247 && TREE_CODE (TREE_TYPE (fndecl)) != METHOD_TYPE)
6248 fndecl = NULL_TREE;
6249 if (fndecl && TYPE_ARG_TYPES (TREE_TYPE (fndecl)))
6250 type = TREE_TYPE (fndecl);
6251 if (fndecl && TREE_CODE (fndecl) != FUNCTION_DECL)
6253 if (TREE_CODE (fndecl) == INDIRECT_REF
6254 && TREE_CODE (TREE_OPERAND (fndecl, 0)) == OBJ_TYPE_REF)
6255 obj_type_ref = TREE_OPERAND (fndecl, 0);
6256 fndecl = NULL_TREE;
6258 if (type)
6260 for (t = TYPE_ARG_TYPES (type); t && t != void_list_node;
6261 t = TREE_CHAIN (t))
6262 if (TREE_CODE (TREE_VALUE (t)) == REFERENCE_TYPE
6263 && INTEGRAL_TYPE_P (TREE_TYPE (TREE_VALUE (t))))
6264 break;
6265 if ((t == NULL || t == void_list_node) && obj_type_ref == NULL_TREE)
6266 type = NULL;
6267 else
6269 int nargs ATTRIBUTE_UNUSED = list_length (TYPE_ARG_TYPES (type));
6270 link = CALL_INSN_FUNCTION_USAGE (insn);
6271 #ifndef PCC_STATIC_STRUCT_RETURN
6272 if (aggregate_value_p (TREE_TYPE (type), type)
6273 && targetm.calls.struct_value_rtx (type, 0) == 0)
6275 tree struct_addr = build_pointer_type (TREE_TYPE (type));
6276 machine_mode mode = TYPE_MODE (struct_addr);
6277 rtx reg;
6278 INIT_CUMULATIVE_ARGS (args_so_far_v, type, NULL_RTX, fndecl,
6279 nargs + 1);
6280 reg = targetm.calls.function_arg (args_so_far, mode,
6281 struct_addr, true);
6282 targetm.calls.function_arg_advance (args_so_far, mode,
6283 struct_addr, true);
6284 if (reg == NULL_RTX)
6286 for (; link; link = XEXP (link, 1))
6287 if (GET_CODE (XEXP (link, 0)) == USE
6288 && MEM_P (XEXP (XEXP (link, 0), 0)))
6290 link = XEXP (link, 1);
6291 break;
6295 else
6296 #endif
6297 INIT_CUMULATIVE_ARGS (args_so_far_v, type, NULL_RTX, fndecl,
6298 nargs);
6299 if (obj_type_ref && TYPE_ARG_TYPES (type) != void_list_node)
6301 machine_mode mode;
6302 t = TYPE_ARG_TYPES (type);
6303 mode = TYPE_MODE (TREE_VALUE (t));
6304 this_arg = targetm.calls.function_arg (args_so_far, mode,
6305 TREE_VALUE (t), true);
6306 if (this_arg && !REG_P (this_arg))
6307 this_arg = NULL_RTX;
6308 else if (this_arg == NULL_RTX)
6310 for (; link; link = XEXP (link, 1))
6311 if (GET_CODE (XEXP (link, 0)) == USE
6312 && MEM_P (XEXP (XEXP (link, 0), 0)))
6314 this_arg = XEXP (XEXP (link, 0), 0);
6315 break;
6322 t = type ? TYPE_ARG_TYPES (type) : NULL_TREE;
6324 for (link = CALL_INSN_FUNCTION_USAGE (insn); link; link = XEXP (link, 1))
6325 if (GET_CODE (XEXP (link, 0)) == USE)
6327 rtx item = NULL_RTX;
6328 x = XEXP (XEXP (link, 0), 0);
6329 if (GET_MODE (link) == VOIDmode
6330 || GET_MODE (link) == BLKmode
6331 || (GET_MODE (link) != GET_MODE (x)
6332 && ((GET_MODE_CLASS (GET_MODE (link)) != MODE_INT
6333 && GET_MODE_CLASS (GET_MODE (link)) != MODE_PARTIAL_INT)
6334 || (GET_MODE_CLASS (GET_MODE (x)) != MODE_INT
6335 && GET_MODE_CLASS (GET_MODE (x)) != MODE_PARTIAL_INT))))
6336 /* Can't do anything for these, if the original type mode
6337 isn't known or can't be converted. */;
6338 else if (REG_P (x))
6340 cselib_val *val = cselib_lookup (x, GET_MODE (x), 0, VOIDmode);
6341 scalar_int_mode mode;
6342 if (val && cselib_preserved_value_p (val))
6343 item = val->val_rtx;
6344 else if (is_a <scalar_int_mode> (GET_MODE (x), &mode))
6346 opt_scalar_int_mode mode_iter;
6347 FOR_EACH_WIDER_MODE (mode_iter, mode)
6349 mode = mode_iter.require ();
6350 if (GET_MODE_BITSIZE (mode) > BITS_PER_WORD)
6351 break;
6353 rtx reg = simplify_subreg (mode, x, GET_MODE (x), 0);
6354 if (reg == NULL_RTX || !REG_P (reg))
6355 continue;
6356 val = cselib_lookup (reg, mode, 0, VOIDmode);
6357 if (val && cselib_preserved_value_p (val))
6359 item = val->val_rtx;
6360 break;
6365 else if (MEM_P (x))
6367 rtx mem = x;
6368 cselib_val *val;
6370 if (!frame_pointer_needed)
6372 struct adjust_mem_data amd;
6373 amd.mem_mode = VOIDmode;
6374 amd.stack_adjust = -VTI (bb)->out.stack_adjust;
6375 amd.store = true;
6376 mem = simplify_replace_fn_rtx (mem, NULL_RTX, adjust_mems,
6377 &amd);
6378 gcc_assert (amd.side_effects.is_empty ());
6380 val = cselib_lookup (mem, GET_MODE (mem), 0, VOIDmode);
6381 if (val && cselib_preserved_value_p (val))
6382 item = val->val_rtx;
6383 else if (GET_MODE_CLASS (GET_MODE (mem)) != MODE_INT
6384 && GET_MODE_CLASS (GET_MODE (mem)) != MODE_PARTIAL_INT)
6386 /* For non-integer stack argument see also if they weren't
6387 initialized by integers. */
6388 scalar_int_mode imode;
6389 if (int_mode_for_mode (GET_MODE (mem)).exists (&imode)
6390 && imode != GET_MODE (mem))
6392 val = cselib_lookup (adjust_address_nv (mem, imode, 0),
6393 imode, 0, VOIDmode);
6394 if (val && cselib_preserved_value_p (val))
6395 item = lowpart_subreg (GET_MODE (x), val->val_rtx,
6396 imode);
6400 if (item)
6402 rtx x2 = x;
6403 if (GET_MODE (item) != GET_MODE (link))
6404 item = lowpart_subreg (GET_MODE (link), item, GET_MODE (item));
6405 if (GET_MODE (x2) != GET_MODE (link))
6406 x2 = lowpart_subreg (GET_MODE (link), x2, GET_MODE (x2));
6407 item = gen_rtx_CONCAT (GET_MODE (link), x2, item);
6408 call_arguments
6409 = gen_rtx_EXPR_LIST (VOIDmode, item, call_arguments);
6411 if (t && t != void_list_node)
6413 tree argtype = TREE_VALUE (t);
6414 machine_mode mode = TYPE_MODE (argtype);
6415 rtx reg;
6416 if (pass_by_reference (&args_so_far_v, mode, argtype, true))
6418 argtype = build_pointer_type (argtype);
6419 mode = TYPE_MODE (argtype);
6421 reg = targetm.calls.function_arg (args_so_far, mode,
6422 argtype, true);
6423 if (TREE_CODE (argtype) == REFERENCE_TYPE
6424 && INTEGRAL_TYPE_P (TREE_TYPE (argtype))
6425 && reg
6426 && REG_P (reg)
6427 && GET_MODE (reg) == mode
6428 && (GET_MODE_CLASS (mode) == MODE_INT
6429 || GET_MODE_CLASS (mode) == MODE_PARTIAL_INT)
6430 && REG_P (x)
6431 && REGNO (x) == REGNO (reg)
6432 && GET_MODE (x) == mode
6433 && item)
6435 machine_mode indmode
6436 = TYPE_MODE (TREE_TYPE (argtype));
6437 rtx mem = gen_rtx_MEM (indmode, x);
6438 cselib_val *val = cselib_lookup (mem, indmode, 0, VOIDmode);
6439 if (val && cselib_preserved_value_p (val))
6441 item = gen_rtx_CONCAT (indmode, mem, val->val_rtx);
6442 call_arguments = gen_rtx_EXPR_LIST (VOIDmode, item,
6443 call_arguments);
6445 else
6447 struct elt_loc_list *l;
6448 tree initial;
6450 /* Try harder, when passing address of a constant
6451 pool integer it can be easily read back. */
6452 item = XEXP (item, 1);
6453 if (GET_CODE (item) == SUBREG)
6454 item = SUBREG_REG (item);
6455 gcc_assert (GET_CODE (item) == VALUE);
6456 val = CSELIB_VAL_PTR (item);
6457 for (l = val->locs; l; l = l->next)
6458 if (GET_CODE (l->loc) == SYMBOL_REF
6459 && TREE_CONSTANT_POOL_ADDRESS_P (l->loc)
6460 && SYMBOL_REF_DECL (l->loc)
6461 && DECL_INITIAL (SYMBOL_REF_DECL (l->loc)))
6463 initial = DECL_INITIAL (SYMBOL_REF_DECL (l->loc));
6464 if (tree_fits_shwi_p (initial))
6466 item = GEN_INT (tree_to_shwi (initial));
6467 item = gen_rtx_CONCAT (indmode, mem, item);
6468 call_arguments
6469 = gen_rtx_EXPR_LIST (VOIDmode, item,
6470 call_arguments);
6472 break;
6476 targetm.calls.function_arg_advance (args_so_far, mode,
6477 argtype, true);
6478 t = TREE_CHAIN (t);
6482 /* Add debug arguments. */
6483 if (fndecl
6484 && TREE_CODE (fndecl) == FUNCTION_DECL
6485 && DECL_HAS_DEBUG_ARGS_P (fndecl))
6487 vec<tree, va_gc> **debug_args = decl_debug_args_lookup (fndecl);
6488 if (debug_args)
6490 unsigned int ix;
6491 tree param;
6492 for (ix = 0; vec_safe_iterate (*debug_args, ix, &param); ix += 2)
6494 rtx item;
6495 tree dtemp = (**debug_args)[ix + 1];
6496 machine_mode mode = DECL_MODE (dtemp);
6497 item = gen_rtx_DEBUG_PARAMETER_REF (mode, param);
6498 item = gen_rtx_CONCAT (mode, item, DECL_RTL_KNOWN_SET (dtemp));
6499 call_arguments = gen_rtx_EXPR_LIST (VOIDmode, item,
6500 call_arguments);
6505 /* Reverse call_arguments chain. */
6506 prev = NULL_RTX;
6507 for (cur = call_arguments; cur; cur = next)
6509 next = XEXP (cur, 1);
6510 XEXP (cur, 1) = prev;
6511 prev = cur;
6513 call_arguments = prev;
6515 x = get_call_rtx_from (insn);
6516 if (x)
6518 x = XEXP (XEXP (x, 0), 0);
6519 if (GET_CODE (x) == SYMBOL_REF)
6520 /* Don't record anything. */;
6521 else if (CONSTANT_P (x))
6523 x = gen_rtx_CONCAT (GET_MODE (x) == VOIDmode ? Pmode : GET_MODE (x),
6524 pc_rtx, x);
6525 call_arguments
6526 = gen_rtx_EXPR_LIST (VOIDmode, x, call_arguments);
6528 else
6530 cselib_val *val = cselib_lookup (x, GET_MODE (x), 0, VOIDmode);
6531 if (val && cselib_preserved_value_p (val))
6533 x = gen_rtx_CONCAT (GET_MODE (x), pc_rtx, val->val_rtx);
6534 call_arguments
6535 = gen_rtx_EXPR_LIST (VOIDmode, x, call_arguments);
6539 if (this_arg)
6541 machine_mode mode
6542 = TYPE_MODE (TREE_TYPE (OBJ_TYPE_REF_EXPR (obj_type_ref)));
6543 rtx clobbered = gen_rtx_MEM (mode, this_arg);
6544 HOST_WIDE_INT token
6545 = tree_to_shwi (OBJ_TYPE_REF_TOKEN (obj_type_ref));
6546 if (token)
6547 clobbered = plus_constant (mode, clobbered,
6548 token * GET_MODE_SIZE (mode));
6549 clobbered = gen_rtx_MEM (mode, clobbered);
6550 x = gen_rtx_CONCAT (mode, gen_rtx_CLOBBER (VOIDmode, pc_rtx), clobbered);
6551 call_arguments
6552 = gen_rtx_EXPR_LIST (VOIDmode, x, call_arguments);
6556 /* Callback for cselib_record_sets_hook, that records as micro
6557 operations uses and stores in an insn after cselib_record_sets has
6558 analyzed the sets in an insn, but before it modifies the stored
6559 values in the internal tables, unless cselib_record_sets doesn't
6560 call it directly (perhaps because we're not doing cselib in the
6561 first place, in which case sets and n_sets will be 0). */
6563 static void
6564 add_with_sets (rtx_insn *insn, struct cselib_set *sets, int n_sets)
6566 basic_block bb = BLOCK_FOR_INSN (insn);
6567 int n1, n2;
6568 struct count_use_info cui;
6569 micro_operation *mos;
6571 cselib_hook_called = true;
6573 cui.insn = insn;
6574 cui.bb = bb;
6575 cui.sets = sets;
6576 cui.n_sets = n_sets;
6578 n1 = VTI (bb)->mos.length ();
6579 cui.store_p = false;
6580 note_uses (&PATTERN (insn), add_uses_1, &cui);
6581 n2 = VTI (bb)->mos.length () - 1;
6582 mos = VTI (bb)->mos.address ();
6584 /* Order the MO_USEs to be before MO_USE_NO_VARs and MO_VAL_USE, and
6585 MO_VAL_LOC last. */
6586 while (n1 < n2)
6588 while (n1 < n2 && mos[n1].type == MO_USE)
6589 n1++;
6590 while (n1 < n2 && mos[n2].type != MO_USE)
6591 n2--;
6592 if (n1 < n2)
6593 std::swap (mos[n1], mos[n2]);
6596 n2 = VTI (bb)->mos.length () - 1;
6597 while (n1 < n2)
6599 while (n1 < n2 && mos[n1].type != MO_VAL_LOC)
6600 n1++;
6601 while (n1 < n2 && mos[n2].type == MO_VAL_LOC)
6602 n2--;
6603 if (n1 < n2)
6604 std::swap (mos[n1], mos[n2]);
6607 if (CALL_P (insn))
6609 micro_operation mo;
6611 mo.type = MO_CALL;
6612 mo.insn = insn;
6613 mo.u.loc = call_arguments;
6614 call_arguments = NULL_RTX;
6616 if (dump_file && (dump_flags & TDF_DETAILS))
6617 log_op_type (PATTERN (insn), bb, insn, mo.type, dump_file);
6618 VTI (bb)->mos.safe_push (mo);
6621 n1 = VTI (bb)->mos.length ();
6622 /* This will record NEXT_INSN (insn), such that we can
6623 insert notes before it without worrying about any
6624 notes that MO_USEs might emit after the insn. */
6625 cui.store_p = true;
6626 note_stores (PATTERN (insn), add_stores, &cui);
6627 n2 = VTI (bb)->mos.length () - 1;
6628 mos = VTI (bb)->mos.address ();
6630 /* Order the MO_VAL_USEs first (note_stores does nothing
6631 on DEBUG_INSNs, so there are no MO_VAL_LOCs from this
6632 insn), then MO_CLOBBERs, then MO_SET/MO_COPY/MO_VAL_SET. */
6633 while (n1 < n2)
6635 while (n1 < n2 && mos[n1].type == MO_VAL_USE)
6636 n1++;
6637 while (n1 < n2 && mos[n2].type != MO_VAL_USE)
6638 n2--;
6639 if (n1 < n2)
6640 std::swap (mos[n1], mos[n2]);
6643 n2 = VTI (bb)->mos.length () - 1;
6644 while (n1 < n2)
6646 while (n1 < n2 && mos[n1].type == MO_CLOBBER)
6647 n1++;
6648 while (n1 < n2 && mos[n2].type != MO_CLOBBER)
6649 n2--;
6650 if (n1 < n2)
6651 std::swap (mos[n1], mos[n2]);
6655 static enum var_init_status
6656 find_src_status (dataflow_set *in, rtx src)
6658 tree decl = NULL_TREE;
6659 enum var_init_status status = VAR_INIT_STATUS_UNINITIALIZED;
6661 if (! flag_var_tracking_uninit)
6662 status = VAR_INIT_STATUS_INITIALIZED;
6664 if (src && REG_P (src))
6665 decl = var_debug_decl (REG_EXPR (src));
6666 else if (src && MEM_P (src))
6667 decl = var_debug_decl (MEM_EXPR (src));
6669 if (src && decl)
6670 status = get_init_value (in, src, dv_from_decl (decl));
6672 return status;
6675 /* SRC is the source of an assignment. Use SET to try to find what
6676 was ultimately assigned to SRC. Return that value if known,
6677 otherwise return SRC itself. */
6679 static rtx
6680 find_src_set_src (dataflow_set *set, rtx src)
6682 tree decl = NULL_TREE; /* The variable being copied around. */
6683 rtx set_src = NULL_RTX; /* The value for "decl" stored in "src". */
6684 variable *var;
6685 location_chain *nextp;
6686 int i;
6687 bool found;
6689 if (src && REG_P (src))
6690 decl = var_debug_decl (REG_EXPR (src));
6691 else if (src && MEM_P (src))
6692 decl = var_debug_decl (MEM_EXPR (src));
6694 if (src && decl)
6696 decl_or_value dv = dv_from_decl (decl);
6698 var = shared_hash_find (set->vars, dv);
6699 if (var)
6701 found = false;
6702 for (i = 0; i < var->n_var_parts && !found; i++)
6703 for (nextp = var->var_part[i].loc_chain; nextp && !found;
6704 nextp = nextp->next)
6705 if (rtx_equal_p (nextp->loc, src))
6707 set_src = nextp->set_src;
6708 found = true;
6714 return set_src;
6717 /* Compute the changes of variable locations in the basic block BB. */
6719 static bool
6720 compute_bb_dataflow (basic_block bb)
6722 unsigned int i;
6723 micro_operation *mo;
6724 bool changed;
6725 dataflow_set old_out;
6726 dataflow_set *in = &VTI (bb)->in;
6727 dataflow_set *out = &VTI (bb)->out;
6729 dataflow_set_init (&old_out);
6730 dataflow_set_copy (&old_out, out);
6731 dataflow_set_copy (out, in);
6733 if (MAY_HAVE_DEBUG_BIND_INSNS)
6734 local_get_addr_cache = new hash_map<rtx, rtx>;
6736 FOR_EACH_VEC_ELT (VTI (bb)->mos, i, mo)
6738 rtx_insn *insn = mo->insn;
6740 switch (mo->type)
6742 case MO_CALL:
6743 dataflow_set_clear_at_call (out, insn);
6744 break;
6746 case MO_USE:
6748 rtx loc = mo->u.loc;
6750 if (REG_P (loc))
6751 var_reg_set (out, loc, VAR_INIT_STATUS_UNINITIALIZED, NULL);
6752 else if (MEM_P (loc))
6753 var_mem_set (out, loc, VAR_INIT_STATUS_UNINITIALIZED, NULL);
6755 break;
6757 case MO_VAL_LOC:
6759 rtx loc = mo->u.loc;
6760 rtx val, vloc;
6761 tree var;
6763 if (GET_CODE (loc) == CONCAT)
6765 val = XEXP (loc, 0);
6766 vloc = XEXP (loc, 1);
6768 else
6770 val = NULL_RTX;
6771 vloc = loc;
6774 var = PAT_VAR_LOCATION_DECL (vloc);
6776 clobber_variable_part (out, NULL_RTX,
6777 dv_from_decl (var), 0, NULL_RTX);
6778 if (val)
6780 if (VAL_NEEDS_RESOLUTION (loc))
6781 val_resolve (out, val, PAT_VAR_LOCATION_LOC (vloc), insn);
6782 set_variable_part (out, val, dv_from_decl (var), 0,
6783 VAR_INIT_STATUS_INITIALIZED, NULL_RTX,
6784 INSERT);
6786 else if (!VAR_LOC_UNKNOWN_P (PAT_VAR_LOCATION_LOC (vloc)))
6787 set_variable_part (out, PAT_VAR_LOCATION_LOC (vloc),
6788 dv_from_decl (var), 0,
6789 VAR_INIT_STATUS_INITIALIZED, NULL_RTX,
6790 INSERT);
6792 break;
6794 case MO_VAL_USE:
6796 rtx loc = mo->u.loc;
6797 rtx val, vloc, uloc;
6799 vloc = uloc = XEXP (loc, 1);
6800 val = XEXP (loc, 0);
6802 if (GET_CODE (val) == CONCAT)
6804 uloc = XEXP (val, 1);
6805 val = XEXP (val, 0);
6808 if (VAL_NEEDS_RESOLUTION (loc))
6809 val_resolve (out, val, vloc, insn);
6810 else
6811 val_store (out, val, uloc, insn, false);
6813 if (VAL_HOLDS_TRACK_EXPR (loc))
6815 if (GET_CODE (uloc) == REG)
6816 var_reg_set (out, uloc, VAR_INIT_STATUS_UNINITIALIZED,
6817 NULL);
6818 else if (GET_CODE (uloc) == MEM)
6819 var_mem_set (out, uloc, VAR_INIT_STATUS_UNINITIALIZED,
6820 NULL);
6823 break;
6825 case MO_VAL_SET:
6827 rtx loc = mo->u.loc;
6828 rtx val, vloc, uloc;
6829 rtx dstv, srcv;
6831 vloc = loc;
6832 uloc = XEXP (vloc, 1);
6833 val = XEXP (vloc, 0);
6834 vloc = uloc;
6836 if (GET_CODE (uloc) == SET)
6838 dstv = SET_DEST (uloc);
6839 srcv = SET_SRC (uloc);
6841 else
6843 dstv = uloc;
6844 srcv = NULL;
6847 if (GET_CODE (val) == CONCAT)
6849 dstv = vloc = XEXP (val, 1);
6850 val = XEXP (val, 0);
6853 if (GET_CODE (vloc) == SET)
6855 srcv = SET_SRC (vloc);
6857 gcc_assert (val != srcv);
6858 gcc_assert (vloc == uloc || VAL_NEEDS_RESOLUTION (loc));
6860 dstv = vloc = SET_DEST (vloc);
6862 if (VAL_NEEDS_RESOLUTION (loc))
6863 val_resolve (out, val, srcv, insn);
6865 else if (VAL_NEEDS_RESOLUTION (loc))
6867 gcc_assert (GET_CODE (uloc) == SET
6868 && GET_CODE (SET_SRC (uloc)) == REG);
6869 val_resolve (out, val, SET_SRC (uloc), insn);
6872 if (VAL_HOLDS_TRACK_EXPR (loc))
6874 if (VAL_EXPR_IS_CLOBBERED (loc))
6876 if (REG_P (uloc))
6877 var_reg_delete (out, uloc, true);
6878 else if (MEM_P (uloc))
6880 gcc_assert (MEM_P (dstv));
6881 gcc_assert (MEM_ATTRS (dstv) == MEM_ATTRS (uloc));
6882 var_mem_delete (out, dstv, true);
6885 else
6887 bool copied_p = VAL_EXPR_IS_COPIED (loc);
6888 rtx src = NULL, dst = uloc;
6889 enum var_init_status status = VAR_INIT_STATUS_INITIALIZED;
6891 if (GET_CODE (uloc) == SET)
6893 src = SET_SRC (uloc);
6894 dst = SET_DEST (uloc);
6897 if (copied_p)
6899 if (flag_var_tracking_uninit)
6901 status = find_src_status (in, src);
6903 if (status == VAR_INIT_STATUS_UNKNOWN)
6904 status = find_src_status (out, src);
6907 src = find_src_set_src (in, src);
6910 if (REG_P (dst))
6911 var_reg_delete_and_set (out, dst, !copied_p,
6912 status, srcv);
6913 else if (MEM_P (dst))
6915 gcc_assert (MEM_P (dstv));
6916 gcc_assert (MEM_ATTRS (dstv) == MEM_ATTRS (dst));
6917 var_mem_delete_and_set (out, dstv, !copied_p,
6918 status, srcv);
6922 else if (REG_P (uloc))
6923 var_regno_delete (out, REGNO (uloc));
6924 else if (MEM_P (uloc))
6926 gcc_checking_assert (GET_CODE (vloc) == MEM);
6927 gcc_checking_assert (dstv == vloc);
6928 if (dstv != vloc)
6929 clobber_overlapping_mems (out, vloc);
6932 val_store (out, val, dstv, insn, true);
6934 break;
6936 case MO_SET:
6938 rtx loc = mo->u.loc;
6939 rtx set_src = NULL;
6941 if (GET_CODE (loc) == SET)
6943 set_src = SET_SRC (loc);
6944 loc = SET_DEST (loc);
6947 if (REG_P (loc))
6948 var_reg_delete_and_set (out, loc, true, VAR_INIT_STATUS_INITIALIZED,
6949 set_src);
6950 else if (MEM_P (loc))
6951 var_mem_delete_and_set (out, loc, true, VAR_INIT_STATUS_INITIALIZED,
6952 set_src);
6954 break;
6956 case MO_COPY:
6958 rtx loc = mo->u.loc;
6959 enum var_init_status src_status;
6960 rtx set_src = NULL;
6962 if (GET_CODE (loc) == SET)
6964 set_src = SET_SRC (loc);
6965 loc = SET_DEST (loc);
6968 if (! flag_var_tracking_uninit)
6969 src_status = VAR_INIT_STATUS_INITIALIZED;
6970 else
6972 src_status = find_src_status (in, set_src);
6974 if (src_status == VAR_INIT_STATUS_UNKNOWN)
6975 src_status = find_src_status (out, set_src);
6978 set_src = find_src_set_src (in, set_src);
6980 if (REG_P (loc))
6981 var_reg_delete_and_set (out, loc, false, src_status, set_src);
6982 else if (MEM_P (loc))
6983 var_mem_delete_and_set (out, loc, false, src_status, set_src);
6985 break;
6987 case MO_USE_NO_VAR:
6989 rtx loc = mo->u.loc;
6991 if (REG_P (loc))
6992 var_reg_delete (out, loc, false);
6993 else if (MEM_P (loc))
6994 var_mem_delete (out, loc, false);
6996 break;
6998 case MO_CLOBBER:
7000 rtx loc = mo->u.loc;
7002 if (REG_P (loc))
7003 var_reg_delete (out, loc, true);
7004 else if (MEM_P (loc))
7005 var_mem_delete (out, loc, true);
7007 break;
7009 case MO_ADJUST:
7010 out->stack_adjust += mo->u.adjust;
7011 break;
7015 if (MAY_HAVE_DEBUG_BIND_INSNS)
7017 delete local_get_addr_cache;
7018 local_get_addr_cache = NULL;
7020 dataflow_set_equiv_regs (out);
7021 shared_hash_htab (out->vars)
7022 ->traverse <dataflow_set *, canonicalize_values_mark> (out);
7023 shared_hash_htab (out->vars)
7024 ->traverse <dataflow_set *, canonicalize_values_star> (out);
7025 if (flag_checking)
7026 shared_hash_htab (out->vars)
7027 ->traverse <dataflow_set *, canonicalize_loc_order_check> (out);
7029 changed = dataflow_set_different (&old_out, out);
7030 dataflow_set_destroy (&old_out);
7031 return changed;
7034 /* Find the locations of variables in the whole function. */
7036 static bool
7037 vt_find_locations (void)
7039 bb_heap_t *worklist = new bb_heap_t (LONG_MIN);
7040 bb_heap_t *pending = new bb_heap_t (LONG_MIN);
7041 sbitmap in_worklist, in_pending;
7042 basic_block bb;
7043 edge e;
7044 int *bb_order;
7045 int *rc_order;
7046 int i;
7047 int htabsz = 0;
7048 int htabmax = PARAM_VALUE (PARAM_MAX_VARTRACK_SIZE);
7049 bool success = true;
7051 timevar_push (TV_VAR_TRACKING_DATAFLOW);
7052 /* Compute reverse completion order of depth first search of the CFG
7053 so that the data-flow runs faster. */
7054 rc_order = XNEWVEC (int, n_basic_blocks_for_fn (cfun) - NUM_FIXED_BLOCKS);
7055 bb_order = XNEWVEC (int, last_basic_block_for_fn (cfun));
7056 pre_and_rev_post_order_compute (NULL, rc_order, false);
7057 for (i = 0; i < n_basic_blocks_for_fn (cfun) - NUM_FIXED_BLOCKS; i++)
7058 bb_order[rc_order[i]] = i;
7059 free (rc_order);
7061 auto_sbitmap visited (last_basic_block_for_fn (cfun));
7062 in_worklist = sbitmap_alloc (last_basic_block_for_fn (cfun));
7063 in_pending = sbitmap_alloc (last_basic_block_for_fn (cfun));
7064 bitmap_clear (in_worklist);
7066 FOR_EACH_BB_FN (bb, cfun)
7067 pending->insert (bb_order[bb->index], bb);
7068 bitmap_ones (in_pending);
7070 while (success && !pending->empty ())
7072 std::swap (worklist, pending);
7073 std::swap (in_worklist, in_pending);
7075 bitmap_clear (visited);
7077 while (!worklist->empty ())
7079 bb = worklist->extract_min ();
7080 bitmap_clear_bit (in_worklist, bb->index);
7081 gcc_assert (!bitmap_bit_p (visited, bb->index));
7082 if (!bitmap_bit_p (visited, bb->index))
7084 bool changed;
7085 edge_iterator ei;
7086 int oldinsz, oldoutsz;
7088 bitmap_set_bit (visited, bb->index);
7090 if (VTI (bb)->in.vars)
7092 htabsz
7093 -= shared_hash_htab (VTI (bb)->in.vars)->size ()
7094 + shared_hash_htab (VTI (bb)->out.vars)->size ();
7095 oldinsz = shared_hash_htab (VTI (bb)->in.vars)->elements ();
7096 oldoutsz
7097 = shared_hash_htab (VTI (bb)->out.vars)->elements ();
7099 else
7100 oldinsz = oldoutsz = 0;
7102 if (MAY_HAVE_DEBUG_BIND_INSNS)
7104 dataflow_set *in = &VTI (bb)->in, *first_out = NULL;
7105 bool first = true, adjust = false;
7107 /* Calculate the IN set as the intersection of
7108 predecessor OUT sets. */
7110 dataflow_set_clear (in);
7111 dst_can_be_shared = true;
7113 FOR_EACH_EDGE (e, ei, bb->preds)
7114 if (!VTI (e->src)->flooded)
7115 gcc_assert (bb_order[bb->index]
7116 <= bb_order[e->src->index]);
7117 else if (first)
7119 dataflow_set_copy (in, &VTI (e->src)->out);
7120 first_out = &VTI (e->src)->out;
7121 first = false;
7123 else
7125 dataflow_set_merge (in, &VTI (e->src)->out);
7126 adjust = true;
7129 if (adjust)
7131 dataflow_post_merge_adjust (in, &VTI (bb)->permp);
7133 if (flag_checking)
7134 /* Merge and merge_adjust should keep entries in
7135 canonical order. */
7136 shared_hash_htab (in->vars)
7137 ->traverse <dataflow_set *,
7138 canonicalize_loc_order_check> (in);
7140 if (dst_can_be_shared)
7142 shared_hash_destroy (in->vars);
7143 in->vars = shared_hash_copy (first_out->vars);
7147 VTI (bb)->flooded = true;
7149 else
7151 /* Calculate the IN set as union of predecessor OUT sets. */
7152 dataflow_set_clear (&VTI (bb)->in);
7153 FOR_EACH_EDGE (e, ei, bb->preds)
7154 dataflow_set_union (&VTI (bb)->in, &VTI (e->src)->out);
7157 changed = compute_bb_dataflow (bb);
7158 htabsz += shared_hash_htab (VTI (bb)->in.vars)->size ()
7159 + shared_hash_htab (VTI (bb)->out.vars)->size ();
7161 if (htabmax && htabsz > htabmax)
7163 if (MAY_HAVE_DEBUG_BIND_INSNS)
7164 inform (DECL_SOURCE_LOCATION (cfun->decl),
7165 "variable tracking size limit exceeded with "
7166 "-fvar-tracking-assignments, retrying without");
7167 else
7168 inform (DECL_SOURCE_LOCATION (cfun->decl),
7169 "variable tracking size limit exceeded");
7170 success = false;
7171 break;
7174 if (changed)
7176 FOR_EACH_EDGE (e, ei, bb->succs)
7178 if (e->dest == EXIT_BLOCK_PTR_FOR_FN (cfun))
7179 continue;
7181 if (bitmap_bit_p (visited, e->dest->index))
7183 if (!bitmap_bit_p (in_pending, e->dest->index))
7185 /* Send E->DEST to next round. */
7186 bitmap_set_bit (in_pending, e->dest->index);
7187 pending->insert (bb_order[e->dest->index],
7188 e->dest);
7191 else if (!bitmap_bit_p (in_worklist, e->dest->index))
7193 /* Add E->DEST to current round. */
7194 bitmap_set_bit (in_worklist, e->dest->index);
7195 worklist->insert (bb_order[e->dest->index],
7196 e->dest);
7201 if (dump_file)
7202 fprintf (dump_file,
7203 "BB %i: in %i (was %i), out %i (was %i), rem %i + %i, tsz %i\n",
7204 bb->index,
7205 (int)shared_hash_htab (VTI (bb)->in.vars)->size (),
7206 oldinsz,
7207 (int)shared_hash_htab (VTI (bb)->out.vars)->size (),
7208 oldoutsz,
7209 (int)worklist->nodes (), (int)pending->nodes (),
7210 htabsz);
7212 if (dump_file && (dump_flags & TDF_DETAILS))
7214 fprintf (dump_file, "BB %i IN:\n", bb->index);
7215 dump_dataflow_set (&VTI (bb)->in);
7216 fprintf (dump_file, "BB %i OUT:\n", bb->index);
7217 dump_dataflow_set (&VTI (bb)->out);
7223 if (success && MAY_HAVE_DEBUG_BIND_INSNS)
7224 FOR_EACH_BB_FN (bb, cfun)
7225 gcc_assert (VTI (bb)->flooded);
7227 free (bb_order);
7228 delete worklist;
7229 delete pending;
7230 sbitmap_free (in_worklist);
7231 sbitmap_free (in_pending);
7233 timevar_pop (TV_VAR_TRACKING_DATAFLOW);
7234 return success;
7237 /* Print the content of the LIST to dump file. */
7239 static void
7240 dump_attrs_list (attrs *list)
7242 for (; list; list = list->next)
7244 if (dv_is_decl_p (list->dv))
7245 print_mem_expr (dump_file, dv_as_decl (list->dv));
7246 else
7247 print_rtl_single (dump_file, dv_as_value (list->dv));
7248 fprintf (dump_file, "+" HOST_WIDE_INT_PRINT_DEC, list->offset);
7250 fprintf (dump_file, "\n");
7253 /* Print the information about variable *SLOT to dump file. */
7256 dump_var_tracking_slot (variable **slot, void *data ATTRIBUTE_UNUSED)
7258 variable *var = *slot;
7260 dump_var (var);
7262 /* Continue traversing the hash table. */
7263 return 1;
7266 /* Print the information about variable VAR to dump file. */
7268 static void
7269 dump_var (variable *var)
7271 int i;
7272 location_chain *node;
7274 if (dv_is_decl_p (var->dv))
7276 const_tree decl = dv_as_decl (var->dv);
7278 if (DECL_NAME (decl))
7280 fprintf (dump_file, " name: %s",
7281 IDENTIFIER_POINTER (DECL_NAME (decl)));
7282 if (dump_flags & TDF_UID)
7283 fprintf (dump_file, "D.%u", DECL_UID (decl));
7285 else if (TREE_CODE (decl) == DEBUG_EXPR_DECL)
7286 fprintf (dump_file, " name: D#%u", DEBUG_TEMP_UID (decl));
7287 else
7288 fprintf (dump_file, " name: D.%u", DECL_UID (decl));
7289 fprintf (dump_file, "\n");
7291 else
7293 fputc (' ', dump_file);
7294 print_rtl_single (dump_file, dv_as_value (var->dv));
7297 for (i = 0; i < var->n_var_parts; i++)
7299 fprintf (dump_file, " offset %ld\n",
7300 (long)(var->onepart ? 0 : VAR_PART_OFFSET (var, i)));
7301 for (node = var->var_part[i].loc_chain; node; node = node->next)
7303 fprintf (dump_file, " ");
7304 if (node->init == VAR_INIT_STATUS_UNINITIALIZED)
7305 fprintf (dump_file, "[uninit]");
7306 print_rtl_single (dump_file, node->loc);
7311 /* Print the information about variables from hash table VARS to dump file. */
7313 static void
7314 dump_vars (variable_table_type *vars)
7316 if (vars->elements () > 0)
7318 fprintf (dump_file, "Variables:\n");
7319 vars->traverse <void *, dump_var_tracking_slot> (NULL);
7323 /* Print the dataflow set SET to dump file. */
7325 static void
7326 dump_dataflow_set (dataflow_set *set)
7328 int i;
7330 fprintf (dump_file, "Stack adjustment: " HOST_WIDE_INT_PRINT_DEC "\n",
7331 set->stack_adjust);
7332 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
7334 if (set->regs[i])
7336 fprintf (dump_file, "Reg %d:", i);
7337 dump_attrs_list (set->regs[i]);
7340 dump_vars (shared_hash_htab (set->vars));
7341 fprintf (dump_file, "\n");
7344 /* Print the IN and OUT sets for each basic block to dump file. */
7346 static void
7347 dump_dataflow_sets (void)
7349 basic_block bb;
7351 FOR_EACH_BB_FN (bb, cfun)
7353 fprintf (dump_file, "\nBasic block %d:\n", bb->index);
7354 fprintf (dump_file, "IN:\n");
7355 dump_dataflow_set (&VTI (bb)->in);
7356 fprintf (dump_file, "OUT:\n");
7357 dump_dataflow_set (&VTI (bb)->out);
7361 /* Return the variable for DV in dropped_values, inserting one if
7362 requested with INSERT. */
7364 static inline variable *
7365 variable_from_dropped (decl_or_value dv, enum insert_option insert)
7367 variable **slot;
7368 variable *empty_var;
7369 onepart_enum onepart;
7371 slot = dropped_values->find_slot_with_hash (dv, dv_htab_hash (dv), insert);
7373 if (!slot)
7374 return NULL;
7376 if (*slot)
7377 return *slot;
7379 gcc_checking_assert (insert == INSERT);
7381 onepart = dv_onepart_p (dv);
7383 gcc_checking_assert (onepart == ONEPART_VALUE || onepart == ONEPART_DEXPR);
7385 empty_var = onepart_pool_allocate (onepart);
7386 empty_var->dv = dv;
7387 empty_var->refcount = 1;
7388 empty_var->n_var_parts = 0;
7389 empty_var->onepart = onepart;
7390 empty_var->in_changed_variables = false;
7391 empty_var->var_part[0].loc_chain = NULL;
7392 empty_var->var_part[0].cur_loc = NULL;
7393 VAR_LOC_1PAUX (empty_var) = NULL;
7394 set_dv_changed (dv, true);
7396 *slot = empty_var;
7398 return empty_var;
7401 /* Recover the one-part aux from dropped_values. */
7403 static struct onepart_aux *
7404 recover_dropped_1paux (variable *var)
7406 variable *dvar;
7408 gcc_checking_assert (var->onepart);
7410 if (VAR_LOC_1PAUX (var))
7411 return VAR_LOC_1PAUX (var);
7413 if (var->onepart == ONEPART_VDECL)
7414 return NULL;
7416 dvar = variable_from_dropped (var->dv, NO_INSERT);
7418 if (!dvar)
7419 return NULL;
7421 VAR_LOC_1PAUX (var) = VAR_LOC_1PAUX (dvar);
7422 VAR_LOC_1PAUX (dvar) = NULL;
7424 return VAR_LOC_1PAUX (var);
7427 /* Add variable VAR to the hash table of changed variables and
7428 if it has no locations delete it from SET's hash table. */
7430 static void
7431 variable_was_changed (variable *var, dataflow_set *set)
7433 hashval_t hash = dv_htab_hash (var->dv);
7435 if (emit_notes)
7437 variable **slot;
7439 /* Remember this decl or VALUE has been added to changed_variables. */
7440 set_dv_changed (var->dv, true);
7442 slot = changed_variables->find_slot_with_hash (var->dv, hash, INSERT);
7444 if (*slot)
7446 variable *old_var = *slot;
7447 gcc_assert (old_var->in_changed_variables);
7448 old_var->in_changed_variables = false;
7449 if (var != old_var && var->onepart)
7451 /* Restore the auxiliary info from an empty variable
7452 previously created for changed_variables, so it is
7453 not lost. */
7454 gcc_checking_assert (!VAR_LOC_1PAUX (var));
7455 VAR_LOC_1PAUX (var) = VAR_LOC_1PAUX (old_var);
7456 VAR_LOC_1PAUX (old_var) = NULL;
7458 variable_htab_free (*slot);
7461 if (set && var->n_var_parts == 0)
7463 onepart_enum onepart = var->onepart;
7464 variable *empty_var = NULL;
7465 variable **dslot = NULL;
7467 if (onepart == ONEPART_VALUE || onepart == ONEPART_DEXPR)
7469 dslot = dropped_values->find_slot_with_hash (var->dv,
7470 dv_htab_hash (var->dv),
7471 INSERT);
7472 empty_var = *dslot;
7474 if (empty_var)
7476 gcc_checking_assert (!empty_var->in_changed_variables);
7477 if (!VAR_LOC_1PAUX (var))
7479 VAR_LOC_1PAUX (var) = VAR_LOC_1PAUX (empty_var);
7480 VAR_LOC_1PAUX (empty_var) = NULL;
7482 else
7483 gcc_checking_assert (!VAR_LOC_1PAUX (empty_var));
7487 if (!empty_var)
7489 empty_var = onepart_pool_allocate (onepart);
7490 empty_var->dv = var->dv;
7491 empty_var->refcount = 1;
7492 empty_var->n_var_parts = 0;
7493 empty_var->onepart = onepart;
7494 if (dslot)
7496 empty_var->refcount++;
7497 *dslot = empty_var;
7500 else
7501 empty_var->refcount++;
7502 empty_var->in_changed_variables = true;
7503 *slot = empty_var;
7504 if (onepart)
7506 empty_var->var_part[0].loc_chain = NULL;
7507 empty_var->var_part[0].cur_loc = NULL;
7508 VAR_LOC_1PAUX (empty_var) = VAR_LOC_1PAUX (var);
7509 VAR_LOC_1PAUX (var) = NULL;
7511 goto drop_var;
7513 else
7515 if (var->onepart && !VAR_LOC_1PAUX (var))
7516 recover_dropped_1paux (var);
7517 var->refcount++;
7518 var->in_changed_variables = true;
7519 *slot = var;
7522 else
7524 gcc_assert (set);
7525 if (var->n_var_parts == 0)
7527 variable **slot;
7529 drop_var:
7530 slot = shared_hash_find_slot_noinsert (set->vars, var->dv);
7531 if (slot)
7533 if (shared_hash_shared (set->vars))
7534 slot = shared_hash_find_slot_unshare (&set->vars, var->dv,
7535 NO_INSERT);
7536 shared_hash_htab (set->vars)->clear_slot (slot);
7542 /* Look for the index in VAR->var_part corresponding to OFFSET.
7543 Return -1 if not found. If INSERTION_POINT is non-NULL, the
7544 referenced int will be set to the index that the part has or should
7545 have, if it should be inserted. */
7547 static inline int
7548 find_variable_location_part (variable *var, HOST_WIDE_INT offset,
7549 int *insertion_point)
7551 int pos, low, high;
7553 if (var->onepart)
7555 if (offset != 0)
7556 return -1;
7558 if (insertion_point)
7559 *insertion_point = 0;
7561 return var->n_var_parts - 1;
7564 /* Find the location part. */
7565 low = 0;
7566 high = var->n_var_parts;
7567 while (low != high)
7569 pos = (low + high) / 2;
7570 if (VAR_PART_OFFSET (var, pos) < offset)
7571 low = pos + 1;
7572 else
7573 high = pos;
7575 pos = low;
7577 if (insertion_point)
7578 *insertion_point = pos;
7580 if (pos < var->n_var_parts && VAR_PART_OFFSET (var, pos) == offset)
7581 return pos;
7583 return -1;
7586 static variable **
7587 set_slot_part (dataflow_set *set, rtx loc, variable **slot,
7588 decl_or_value dv, HOST_WIDE_INT offset,
7589 enum var_init_status initialized, rtx set_src)
7591 int pos;
7592 location_chain *node, *next;
7593 location_chain **nextp;
7594 variable *var;
7595 onepart_enum onepart;
7597 var = *slot;
7599 if (var)
7600 onepart = var->onepart;
7601 else
7602 onepart = dv_onepart_p (dv);
7604 gcc_checking_assert (offset == 0 || !onepart);
7605 gcc_checking_assert (loc != dv_as_opaque (dv));
7607 if (! flag_var_tracking_uninit)
7608 initialized = VAR_INIT_STATUS_INITIALIZED;
7610 if (!var)
7612 /* Create new variable information. */
7613 var = onepart_pool_allocate (onepart);
7614 var->dv = dv;
7615 var->refcount = 1;
7616 var->n_var_parts = 1;
7617 var->onepart = onepart;
7618 var->in_changed_variables = false;
7619 if (var->onepart)
7620 VAR_LOC_1PAUX (var) = NULL;
7621 else
7622 VAR_PART_OFFSET (var, 0) = offset;
7623 var->var_part[0].loc_chain = NULL;
7624 var->var_part[0].cur_loc = NULL;
7625 *slot = var;
7626 pos = 0;
7627 nextp = &var->var_part[0].loc_chain;
7629 else if (onepart)
7631 int r = -1, c = 0;
7633 gcc_assert (dv_as_opaque (var->dv) == dv_as_opaque (dv));
7635 pos = 0;
7637 if (GET_CODE (loc) == VALUE)
7639 for (nextp = &var->var_part[0].loc_chain; (node = *nextp);
7640 nextp = &node->next)
7641 if (GET_CODE (node->loc) == VALUE)
7643 if (node->loc == loc)
7645 r = 0;
7646 break;
7648 if (canon_value_cmp (node->loc, loc))
7649 c++;
7650 else
7652 r = 1;
7653 break;
7656 else if (REG_P (node->loc) || MEM_P (node->loc))
7657 c++;
7658 else
7660 r = 1;
7661 break;
7664 else if (REG_P (loc))
7666 for (nextp = &var->var_part[0].loc_chain; (node = *nextp);
7667 nextp = &node->next)
7668 if (REG_P (node->loc))
7670 if (REGNO (node->loc) < REGNO (loc))
7671 c++;
7672 else
7674 if (REGNO (node->loc) == REGNO (loc))
7675 r = 0;
7676 else
7677 r = 1;
7678 break;
7681 else
7683 r = 1;
7684 break;
7687 else if (MEM_P (loc))
7689 for (nextp = &var->var_part[0].loc_chain; (node = *nextp);
7690 nextp = &node->next)
7691 if (REG_P (node->loc))
7692 c++;
7693 else if (MEM_P (node->loc))
7695 if ((r = loc_cmp (XEXP (node->loc, 0), XEXP (loc, 0))) >= 0)
7696 break;
7697 else
7698 c++;
7700 else
7702 r = 1;
7703 break;
7706 else
7707 for (nextp = &var->var_part[0].loc_chain; (node = *nextp);
7708 nextp = &node->next)
7709 if ((r = loc_cmp (node->loc, loc)) >= 0)
7710 break;
7711 else
7712 c++;
7714 if (r == 0)
7715 return slot;
7717 if (shared_var_p (var, set->vars))
7719 slot = unshare_variable (set, slot, var, initialized);
7720 var = *slot;
7721 for (nextp = &var->var_part[0].loc_chain; c;
7722 nextp = &(*nextp)->next)
7723 c--;
7724 gcc_assert ((!node && !*nextp) || node->loc == (*nextp)->loc);
7727 else
7729 int inspos = 0;
7731 gcc_assert (dv_as_decl (var->dv) == dv_as_decl (dv));
7733 pos = find_variable_location_part (var, offset, &inspos);
7735 if (pos >= 0)
7737 node = var->var_part[pos].loc_chain;
7739 if (node
7740 && ((REG_P (node->loc) && REG_P (loc)
7741 && REGNO (node->loc) == REGNO (loc))
7742 || rtx_equal_p (node->loc, loc)))
7744 /* LOC is in the beginning of the chain so we have nothing
7745 to do. */
7746 if (node->init < initialized)
7747 node->init = initialized;
7748 if (set_src != NULL)
7749 node->set_src = set_src;
7751 return slot;
7753 else
7755 /* We have to make a copy of a shared variable. */
7756 if (shared_var_p (var, set->vars))
7758 slot = unshare_variable (set, slot, var, initialized);
7759 var = *slot;
7763 else
7765 /* We have not found the location part, new one will be created. */
7767 /* We have to make a copy of the shared variable. */
7768 if (shared_var_p (var, set->vars))
7770 slot = unshare_variable (set, slot, var, initialized);
7771 var = *slot;
7774 /* We track only variables whose size is <= MAX_VAR_PARTS bytes
7775 thus there are at most MAX_VAR_PARTS different offsets. */
7776 gcc_assert (var->n_var_parts < MAX_VAR_PARTS
7777 && (!var->n_var_parts || !onepart));
7779 /* We have to move the elements of array starting at index
7780 inspos to the next position. */
7781 for (pos = var->n_var_parts; pos > inspos; pos--)
7782 var->var_part[pos] = var->var_part[pos - 1];
7784 var->n_var_parts++;
7785 gcc_checking_assert (!onepart);
7786 VAR_PART_OFFSET (var, pos) = offset;
7787 var->var_part[pos].loc_chain = NULL;
7788 var->var_part[pos].cur_loc = NULL;
7791 /* Delete the location from the list. */
7792 nextp = &var->var_part[pos].loc_chain;
7793 for (node = var->var_part[pos].loc_chain; node; node = next)
7795 next = node->next;
7796 if ((REG_P (node->loc) && REG_P (loc)
7797 && REGNO (node->loc) == REGNO (loc))
7798 || rtx_equal_p (node->loc, loc))
7800 /* Save these values, to assign to the new node, before
7801 deleting this one. */
7802 if (node->init > initialized)
7803 initialized = node->init;
7804 if (node->set_src != NULL && set_src == NULL)
7805 set_src = node->set_src;
7806 if (var->var_part[pos].cur_loc == node->loc)
7807 var->var_part[pos].cur_loc = NULL;
7808 delete node;
7809 *nextp = next;
7810 break;
7812 else
7813 nextp = &node->next;
7816 nextp = &var->var_part[pos].loc_chain;
7819 /* Add the location to the beginning. */
7820 node = new location_chain;
7821 node->loc = loc;
7822 node->init = initialized;
7823 node->set_src = set_src;
7824 node->next = *nextp;
7825 *nextp = node;
7827 /* If no location was emitted do so. */
7828 if (var->var_part[pos].cur_loc == NULL)
7829 variable_was_changed (var, set);
7831 return slot;
7834 /* Set the part of variable's location in the dataflow set SET. The
7835 variable part is specified by variable's declaration in DV and
7836 offset OFFSET and the part's location by LOC. IOPT should be
7837 NO_INSERT if the variable is known to be in SET already and the
7838 variable hash table must not be resized, and INSERT otherwise. */
7840 static void
7841 set_variable_part (dataflow_set *set, rtx loc,
7842 decl_or_value dv, HOST_WIDE_INT offset,
7843 enum var_init_status initialized, rtx set_src,
7844 enum insert_option iopt)
7846 variable **slot;
7848 if (iopt == NO_INSERT)
7849 slot = shared_hash_find_slot_noinsert (set->vars, dv);
7850 else
7852 slot = shared_hash_find_slot (set->vars, dv);
7853 if (!slot)
7854 slot = shared_hash_find_slot_unshare (&set->vars, dv, iopt);
7856 set_slot_part (set, loc, slot, dv, offset, initialized, set_src);
7859 /* Remove all recorded register locations for the given variable part
7860 from dataflow set SET, except for those that are identical to loc.
7861 The variable part is specified by variable's declaration or value
7862 DV and offset OFFSET. */
7864 static variable **
7865 clobber_slot_part (dataflow_set *set, rtx loc, variable **slot,
7866 HOST_WIDE_INT offset, rtx set_src)
7868 variable *var = *slot;
7869 int pos = find_variable_location_part (var, offset, NULL);
7871 if (pos >= 0)
7873 location_chain *node, *next;
7875 /* Remove the register locations from the dataflow set. */
7876 next = var->var_part[pos].loc_chain;
7877 for (node = next; node; node = next)
7879 next = node->next;
7880 if (node->loc != loc
7881 && (!flag_var_tracking_uninit
7882 || !set_src
7883 || MEM_P (set_src)
7884 || !rtx_equal_p (set_src, node->set_src)))
7886 if (REG_P (node->loc))
7888 attrs *anode, *anext;
7889 attrs **anextp;
7891 /* Remove the variable part from the register's
7892 list, but preserve any other variable parts
7893 that might be regarded as live in that same
7894 register. */
7895 anextp = &set->regs[REGNO (node->loc)];
7896 for (anode = *anextp; anode; anode = anext)
7898 anext = anode->next;
7899 if (dv_as_opaque (anode->dv) == dv_as_opaque (var->dv)
7900 && anode->offset == offset)
7902 delete anode;
7903 *anextp = anext;
7905 else
7906 anextp = &anode->next;
7910 slot = delete_slot_part (set, node->loc, slot, offset);
7915 return slot;
7918 /* Remove all recorded register locations for the given variable part
7919 from dataflow set SET, except for those that are identical to loc.
7920 The variable part is specified by variable's declaration or value
7921 DV and offset OFFSET. */
7923 static void
7924 clobber_variable_part (dataflow_set *set, rtx loc, decl_or_value dv,
7925 HOST_WIDE_INT offset, rtx set_src)
7927 variable **slot;
7929 if (!dv_as_opaque (dv)
7930 || (!dv_is_value_p (dv) && ! DECL_P (dv_as_decl (dv))))
7931 return;
7933 slot = shared_hash_find_slot_noinsert (set->vars, dv);
7934 if (!slot)
7935 return;
7937 clobber_slot_part (set, loc, slot, offset, set_src);
7940 /* Delete the part of variable's location from dataflow set SET. The
7941 variable part is specified by its SET->vars slot SLOT and offset
7942 OFFSET and the part's location by LOC. */
7944 static variable **
7945 delete_slot_part (dataflow_set *set, rtx loc, variable **slot,
7946 HOST_WIDE_INT offset)
7948 variable *var = *slot;
7949 int pos = find_variable_location_part (var, offset, NULL);
7951 if (pos >= 0)
7953 location_chain *node, *next;
7954 location_chain **nextp;
7955 bool changed;
7956 rtx cur_loc;
7958 if (shared_var_p (var, set->vars))
7960 /* If the variable contains the location part we have to
7961 make a copy of the variable. */
7962 for (node = var->var_part[pos].loc_chain; node;
7963 node = node->next)
7965 if ((REG_P (node->loc) && REG_P (loc)
7966 && REGNO (node->loc) == REGNO (loc))
7967 || rtx_equal_p (node->loc, loc))
7969 slot = unshare_variable (set, slot, var,
7970 VAR_INIT_STATUS_UNKNOWN);
7971 var = *slot;
7972 break;
7977 if (pos == 0 && var->onepart && VAR_LOC_1PAUX (var))
7978 cur_loc = VAR_LOC_FROM (var);
7979 else
7980 cur_loc = var->var_part[pos].cur_loc;
7982 /* Delete the location part. */
7983 changed = false;
7984 nextp = &var->var_part[pos].loc_chain;
7985 for (node = *nextp; node; node = next)
7987 next = node->next;
7988 if ((REG_P (node->loc) && REG_P (loc)
7989 && REGNO (node->loc) == REGNO (loc))
7990 || rtx_equal_p (node->loc, loc))
7992 /* If we have deleted the location which was last emitted
7993 we have to emit new location so add the variable to set
7994 of changed variables. */
7995 if (cur_loc == node->loc)
7997 changed = true;
7998 var->var_part[pos].cur_loc = NULL;
7999 if (pos == 0 && var->onepart && VAR_LOC_1PAUX (var))
8000 VAR_LOC_FROM (var) = NULL;
8002 delete node;
8003 *nextp = next;
8004 break;
8006 else
8007 nextp = &node->next;
8010 if (var->var_part[pos].loc_chain == NULL)
8012 changed = true;
8013 var->n_var_parts--;
8014 while (pos < var->n_var_parts)
8016 var->var_part[pos] = var->var_part[pos + 1];
8017 pos++;
8020 if (changed)
8021 variable_was_changed (var, set);
8024 return slot;
8027 /* Delete the part of variable's location from dataflow set SET. The
8028 variable part is specified by variable's declaration or value DV
8029 and offset OFFSET and the part's location by LOC. */
8031 static void
8032 delete_variable_part (dataflow_set *set, rtx loc, decl_or_value dv,
8033 HOST_WIDE_INT offset)
8035 variable **slot = shared_hash_find_slot_noinsert (set->vars, dv);
8036 if (!slot)
8037 return;
8039 delete_slot_part (set, loc, slot, offset);
8043 /* Structure for passing some other parameters to function
8044 vt_expand_loc_callback. */
8045 struct expand_loc_callback_data
8047 /* The variables and values active at this point. */
8048 variable_table_type *vars;
8050 /* Stack of values and debug_exprs under expansion, and their
8051 children. */
8052 auto_vec<rtx, 4> expanding;
8054 /* Stack of values and debug_exprs whose expansion hit recursion
8055 cycles. They will have VALUE_RECURSED_INTO marked when added to
8056 this list. This flag will be cleared if any of its dependencies
8057 resolves to a valid location. So, if the flag remains set at the
8058 end of the search, we know no valid location for this one can
8059 possibly exist. */
8060 auto_vec<rtx, 4> pending;
8062 /* The maximum depth among the sub-expressions under expansion.
8063 Zero indicates no expansion so far. */
8064 expand_depth depth;
8067 /* Allocate the one-part auxiliary data structure for VAR, with enough
8068 room for COUNT dependencies. */
8070 static void
8071 loc_exp_dep_alloc (variable *var, int count)
8073 size_t allocsize;
8075 gcc_checking_assert (var->onepart);
8077 /* We can be called with COUNT == 0 to allocate the data structure
8078 without any dependencies, e.g. for the backlinks only. However,
8079 if we are specifying a COUNT, then the dependency list must have
8080 been emptied before. It would be possible to adjust pointers or
8081 force it empty here, but this is better done at an earlier point
8082 in the algorithm, so we instead leave an assertion to catch
8083 errors. */
8084 gcc_checking_assert (!count
8085 || VAR_LOC_DEP_VEC (var) == NULL
8086 || VAR_LOC_DEP_VEC (var)->is_empty ());
8088 if (VAR_LOC_1PAUX (var) && VAR_LOC_DEP_VEC (var)->space (count))
8089 return;
8091 allocsize = offsetof (struct onepart_aux, deps)
8092 + vec<loc_exp_dep, va_heap, vl_embed>::embedded_size (count);
8094 if (VAR_LOC_1PAUX (var))
8096 VAR_LOC_1PAUX (var) = XRESIZEVAR (struct onepart_aux,
8097 VAR_LOC_1PAUX (var), allocsize);
8098 /* If the reallocation moves the onepaux structure, the
8099 back-pointer to BACKLINKS in the first list member will still
8100 point to its old location. Adjust it. */
8101 if (VAR_LOC_DEP_LST (var))
8102 VAR_LOC_DEP_LST (var)->pprev = VAR_LOC_DEP_LSTP (var);
8104 else
8106 VAR_LOC_1PAUX (var) = XNEWVAR (struct onepart_aux, allocsize);
8107 *VAR_LOC_DEP_LSTP (var) = NULL;
8108 VAR_LOC_FROM (var) = NULL;
8109 VAR_LOC_DEPTH (var).complexity = 0;
8110 VAR_LOC_DEPTH (var).entryvals = 0;
8112 VAR_LOC_DEP_VEC (var)->embedded_init (count);
8115 /* Remove all entries from the vector of active dependencies of VAR,
8116 removing them from the back-links lists too. */
8118 static void
8119 loc_exp_dep_clear (variable *var)
8121 while (VAR_LOC_DEP_VEC (var) && !VAR_LOC_DEP_VEC (var)->is_empty ())
8123 loc_exp_dep *led = &VAR_LOC_DEP_VEC (var)->last ();
8124 if (led->next)
8125 led->next->pprev = led->pprev;
8126 if (led->pprev)
8127 *led->pprev = led->next;
8128 VAR_LOC_DEP_VEC (var)->pop ();
8132 /* Insert an active dependency from VAR on X to the vector of
8133 dependencies, and add the corresponding back-link to X's list of
8134 back-links in VARS. */
8136 static void
8137 loc_exp_insert_dep (variable *var, rtx x, variable_table_type *vars)
8139 decl_or_value dv;
8140 variable *xvar;
8141 loc_exp_dep *led;
8143 dv = dv_from_rtx (x);
8145 /* ??? Build a vector of variables parallel to EXPANDING, to avoid
8146 an additional look up? */
8147 xvar = vars->find_with_hash (dv, dv_htab_hash (dv));
8149 if (!xvar)
8151 xvar = variable_from_dropped (dv, NO_INSERT);
8152 gcc_checking_assert (xvar);
8155 /* No point in adding the same backlink more than once. This may
8156 arise if say the same value appears in two complex expressions in
8157 the same loc_list, or even more than once in a single
8158 expression. */
8159 if (VAR_LOC_DEP_LST (xvar) && VAR_LOC_DEP_LST (xvar)->dv == var->dv)
8160 return;
8162 if (var->onepart == NOT_ONEPART)
8163 led = new loc_exp_dep;
8164 else
8166 loc_exp_dep empty;
8167 memset (&empty, 0, sizeof (empty));
8168 VAR_LOC_DEP_VEC (var)->quick_push (empty);
8169 led = &VAR_LOC_DEP_VEC (var)->last ();
8171 led->dv = var->dv;
8172 led->value = x;
8174 loc_exp_dep_alloc (xvar, 0);
8175 led->pprev = VAR_LOC_DEP_LSTP (xvar);
8176 led->next = *led->pprev;
8177 if (led->next)
8178 led->next->pprev = &led->next;
8179 *led->pprev = led;
8182 /* Create active dependencies of VAR on COUNT values starting at
8183 VALUE, and corresponding back-links to the entries in VARS. Return
8184 true if we found any pending-recursion results. */
8186 static bool
8187 loc_exp_dep_set (variable *var, rtx result, rtx *value, int count,
8188 variable_table_type *vars)
8190 bool pending_recursion = false;
8192 gcc_checking_assert (VAR_LOC_DEP_VEC (var) == NULL
8193 || VAR_LOC_DEP_VEC (var)->is_empty ());
8195 /* Set up all dependencies from last_child (as set up at the end of
8196 the loop above) to the end. */
8197 loc_exp_dep_alloc (var, count);
8199 while (count--)
8201 rtx x = *value++;
8203 if (!pending_recursion)
8204 pending_recursion = !result && VALUE_RECURSED_INTO (x);
8206 loc_exp_insert_dep (var, x, vars);
8209 return pending_recursion;
8212 /* Notify the back-links of IVAR that are pending recursion that we
8213 have found a non-NIL value for it, so they are cleared for another
8214 attempt to compute a current location. */
8216 static void
8217 notify_dependents_of_resolved_value (variable *ivar, variable_table_type *vars)
8219 loc_exp_dep *led, *next;
8221 for (led = VAR_LOC_DEP_LST (ivar); led; led = next)
8223 decl_or_value dv = led->dv;
8224 variable *var;
8226 next = led->next;
8228 if (dv_is_value_p (dv))
8230 rtx value = dv_as_value (dv);
8232 /* If we have already resolved it, leave it alone. */
8233 if (!VALUE_RECURSED_INTO (value))
8234 continue;
8236 /* Check that VALUE_RECURSED_INTO, true from the test above,
8237 implies NO_LOC_P. */
8238 gcc_checking_assert (NO_LOC_P (value));
8240 /* We won't notify variables that are being expanded,
8241 because their dependency list is cleared before
8242 recursing. */
8243 NO_LOC_P (value) = false;
8244 VALUE_RECURSED_INTO (value) = false;
8246 gcc_checking_assert (dv_changed_p (dv));
8248 else
8250 gcc_checking_assert (dv_onepart_p (dv) != NOT_ONEPART);
8251 if (!dv_changed_p (dv))
8252 continue;
8255 var = vars->find_with_hash (dv, dv_htab_hash (dv));
8257 if (!var)
8258 var = variable_from_dropped (dv, NO_INSERT);
8260 if (var)
8261 notify_dependents_of_resolved_value (var, vars);
8263 if (next)
8264 next->pprev = led->pprev;
8265 if (led->pprev)
8266 *led->pprev = next;
8267 led->next = NULL;
8268 led->pprev = NULL;
8272 static rtx vt_expand_loc_callback (rtx x, bitmap regs,
8273 int max_depth, void *data);
8275 /* Return the combined depth, when one sub-expression evaluated to
8276 BEST_DEPTH and the previous known depth was SAVED_DEPTH. */
8278 static inline expand_depth
8279 update_depth (expand_depth saved_depth, expand_depth best_depth)
8281 /* If we didn't find anything, stick with what we had. */
8282 if (!best_depth.complexity)
8283 return saved_depth;
8285 /* If we found hadn't found anything, use the depth of the current
8286 expression. Do NOT add one extra level, we want to compute the
8287 maximum depth among sub-expressions. We'll increment it later,
8288 if appropriate. */
8289 if (!saved_depth.complexity)
8290 return best_depth;
8292 /* Combine the entryval count so that regardless of which one we
8293 return, the entryval count is accurate. */
8294 best_depth.entryvals = saved_depth.entryvals
8295 = best_depth.entryvals + saved_depth.entryvals;
8297 if (saved_depth.complexity < best_depth.complexity)
8298 return best_depth;
8299 else
8300 return saved_depth;
8303 /* Expand VAR to a location RTX, updating its cur_loc. Use REGS and
8304 DATA for cselib expand callback. If PENDRECP is given, indicate in
8305 it whether any sub-expression couldn't be fully evaluated because
8306 it is pending recursion resolution. */
8308 static inline rtx
8309 vt_expand_var_loc_chain (variable *var, bitmap regs, void *data,
8310 bool *pendrecp)
8312 struct expand_loc_callback_data *elcd
8313 = (struct expand_loc_callback_data *) data;
8314 location_chain *loc, *next;
8315 rtx result = NULL;
8316 int first_child, result_first_child, last_child;
8317 bool pending_recursion;
8318 rtx loc_from = NULL;
8319 struct elt_loc_list *cloc = NULL;
8320 expand_depth depth = { 0, 0 }, saved_depth = elcd->depth;
8321 int wanted_entryvals, found_entryvals = 0;
8323 /* Clear all backlinks pointing at this, so that we're not notified
8324 while we're active. */
8325 loc_exp_dep_clear (var);
8327 retry:
8328 if (var->onepart == ONEPART_VALUE)
8330 cselib_val *val = CSELIB_VAL_PTR (dv_as_value (var->dv));
8332 gcc_checking_assert (cselib_preserved_value_p (val));
8334 cloc = val->locs;
8337 first_child = result_first_child = last_child
8338 = elcd->expanding.length ();
8340 wanted_entryvals = found_entryvals;
8342 /* Attempt to expand each available location in turn. */
8343 for (next = loc = var->n_var_parts ? var->var_part[0].loc_chain : NULL;
8344 loc || cloc; loc = next)
8346 result_first_child = last_child;
8348 if (!loc)
8350 loc_from = cloc->loc;
8351 next = loc;
8352 cloc = cloc->next;
8353 if (unsuitable_loc (loc_from))
8354 continue;
8356 else
8358 loc_from = loc->loc;
8359 next = loc->next;
8362 gcc_checking_assert (!unsuitable_loc (loc_from));
8364 elcd->depth.complexity = elcd->depth.entryvals = 0;
8365 result = cselib_expand_value_rtx_cb (loc_from, regs, EXPR_DEPTH,
8366 vt_expand_loc_callback, data);
8367 last_child = elcd->expanding.length ();
8369 if (result)
8371 depth = elcd->depth;
8373 gcc_checking_assert (depth.complexity
8374 || result_first_child == last_child);
8376 if (last_child - result_first_child != 1)
8378 if (!depth.complexity && GET_CODE (result) == ENTRY_VALUE)
8379 depth.entryvals++;
8380 depth.complexity++;
8383 if (depth.complexity <= EXPR_USE_DEPTH)
8385 if (depth.entryvals <= wanted_entryvals)
8386 break;
8387 else if (!found_entryvals || depth.entryvals < found_entryvals)
8388 found_entryvals = depth.entryvals;
8391 result = NULL;
8394 /* Set it up in case we leave the loop. */
8395 depth.complexity = depth.entryvals = 0;
8396 loc_from = NULL;
8397 result_first_child = first_child;
8400 if (!loc_from && wanted_entryvals < found_entryvals)
8402 /* We found entries with ENTRY_VALUEs and skipped them. Since
8403 we could not find any expansions without ENTRY_VALUEs, but we
8404 found at least one with them, go back and get an entry with
8405 the minimum number ENTRY_VALUE count that we found. We could
8406 avoid looping, but since each sub-loc is already resolved,
8407 the re-expansion should be trivial. ??? Should we record all
8408 attempted locs as dependencies, so that we retry the
8409 expansion should any of them change, in the hope it can give
8410 us a new entry without an ENTRY_VALUE? */
8411 elcd->expanding.truncate (first_child);
8412 goto retry;
8415 /* Register all encountered dependencies as active. */
8416 pending_recursion = loc_exp_dep_set
8417 (var, result, elcd->expanding.address () + result_first_child,
8418 last_child - result_first_child, elcd->vars);
8420 elcd->expanding.truncate (first_child);
8422 /* Record where the expansion came from. */
8423 gcc_checking_assert (!result || !pending_recursion);
8424 VAR_LOC_FROM (var) = loc_from;
8425 VAR_LOC_DEPTH (var) = depth;
8427 gcc_checking_assert (!depth.complexity == !result);
8429 elcd->depth = update_depth (saved_depth, depth);
8431 /* Indicate whether any of the dependencies are pending recursion
8432 resolution. */
8433 if (pendrecp)
8434 *pendrecp = pending_recursion;
8436 if (!pendrecp || !pending_recursion)
8437 var->var_part[0].cur_loc = result;
8439 return result;
8442 /* Callback for cselib_expand_value, that looks for expressions
8443 holding the value in the var-tracking hash tables. Return X for
8444 standard processing, anything else is to be used as-is. */
8446 static rtx
8447 vt_expand_loc_callback (rtx x, bitmap regs,
8448 int max_depth ATTRIBUTE_UNUSED,
8449 void *data)
8451 struct expand_loc_callback_data *elcd
8452 = (struct expand_loc_callback_data *) data;
8453 decl_or_value dv;
8454 variable *var;
8455 rtx result, subreg;
8456 bool pending_recursion = false;
8457 bool from_empty = false;
8459 switch (GET_CODE (x))
8461 case SUBREG:
8462 subreg = cselib_expand_value_rtx_cb (SUBREG_REG (x), regs,
8463 EXPR_DEPTH,
8464 vt_expand_loc_callback, data);
8466 if (!subreg)
8467 return NULL;
8469 result = simplify_gen_subreg (GET_MODE (x), subreg,
8470 GET_MODE (SUBREG_REG (x)),
8471 SUBREG_BYTE (x));
8473 /* Invalid SUBREGs are ok in debug info. ??? We could try
8474 alternate expansions for the VALUE as well. */
8475 if (!result)
8476 result = gen_rtx_raw_SUBREG (GET_MODE (x), subreg, SUBREG_BYTE (x));
8478 return result;
8480 case DEBUG_EXPR:
8481 case VALUE:
8482 dv = dv_from_rtx (x);
8483 break;
8485 default:
8486 return x;
8489 elcd->expanding.safe_push (x);
8491 /* Check that VALUE_RECURSED_INTO implies NO_LOC_P. */
8492 gcc_checking_assert (!VALUE_RECURSED_INTO (x) || NO_LOC_P (x));
8494 if (NO_LOC_P (x))
8496 gcc_checking_assert (VALUE_RECURSED_INTO (x) || !dv_changed_p (dv));
8497 return NULL;
8500 var = elcd->vars->find_with_hash (dv, dv_htab_hash (dv));
8502 if (!var)
8504 from_empty = true;
8505 var = variable_from_dropped (dv, INSERT);
8508 gcc_checking_assert (var);
8510 if (!dv_changed_p (dv))
8512 gcc_checking_assert (!NO_LOC_P (x));
8513 gcc_checking_assert (var->var_part[0].cur_loc);
8514 gcc_checking_assert (VAR_LOC_1PAUX (var));
8515 gcc_checking_assert (VAR_LOC_1PAUX (var)->depth.complexity);
8517 elcd->depth = update_depth (elcd->depth, VAR_LOC_1PAUX (var)->depth);
8519 return var->var_part[0].cur_loc;
8522 VALUE_RECURSED_INTO (x) = true;
8523 /* This is tentative, but it makes some tests simpler. */
8524 NO_LOC_P (x) = true;
8526 gcc_checking_assert (var->n_var_parts == 1 || from_empty);
8528 result = vt_expand_var_loc_chain (var, regs, data, &pending_recursion);
8530 if (pending_recursion)
8532 gcc_checking_assert (!result);
8533 elcd->pending.safe_push (x);
8535 else
8537 NO_LOC_P (x) = !result;
8538 VALUE_RECURSED_INTO (x) = false;
8539 set_dv_changed (dv, false);
8541 if (result)
8542 notify_dependents_of_resolved_value (var, elcd->vars);
8545 return result;
8548 /* While expanding variables, we may encounter recursion cycles
8549 because of mutual (possibly indirect) dependencies between two
8550 particular variables (or values), say A and B. If we're trying to
8551 expand A when we get to B, which in turn attempts to expand A, if
8552 we can't find any other expansion for B, we'll add B to this
8553 pending-recursion stack, and tentatively return NULL for its
8554 location. This tentative value will be used for any other
8555 occurrences of B, unless A gets some other location, in which case
8556 it will notify B that it is worth another try at computing a
8557 location for it, and it will use the location computed for A then.
8558 At the end of the expansion, the tentative NULL locations become
8559 final for all members of PENDING that didn't get a notification.
8560 This function performs this finalization of NULL locations. */
8562 static void
8563 resolve_expansions_pending_recursion (vec<rtx, va_heap> *pending)
8565 while (!pending->is_empty ())
8567 rtx x = pending->pop ();
8568 decl_or_value dv;
8570 if (!VALUE_RECURSED_INTO (x))
8571 continue;
8573 gcc_checking_assert (NO_LOC_P (x));
8574 VALUE_RECURSED_INTO (x) = false;
8575 dv = dv_from_rtx (x);
8576 gcc_checking_assert (dv_changed_p (dv));
8577 set_dv_changed (dv, false);
8581 /* Initialize expand_loc_callback_data D with variable hash table V.
8582 It must be a macro because of alloca (vec stack). */
8583 #define INIT_ELCD(d, v) \
8584 do \
8586 (d).vars = (v); \
8587 (d).depth.complexity = (d).depth.entryvals = 0; \
8589 while (0)
8590 /* Finalize expand_loc_callback_data D, resolved to location L. */
8591 #define FINI_ELCD(d, l) \
8592 do \
8594 resolve_expansions_pending_recursion (&(d).pending); \
8595 (d).pending.release (); \
8596 (d).expanding.release (); \
8598 if ((l) && MEM_P (l)) \
8599 (l) = targetm.delegitimize_address (l); \
8601 while (0)
8603 /* Expand VALUEs and DEBUG_EXPRs in LOC to a location, using the
8604 equivalences in VARS, updating their CUR_LOCs in the process. */
8606 static rtx
8607 vt_expand_loc (rtx loc, variable_table_type *vars)
8609 struct expand_loc_callback_data data;
8610 rtx result;
8612 if (!MAY_HAVE_DEBUG_BIND_INSNS)
8613 return loc;
8615 INIT_ELCD (data, vars);
8617 result = cselib_expand_value_rtx_cb (loc, scratch_regs, EXPR_DEPTH,
8618 vt_expand_loc_callback, &data);
8620 FINI_ELCD (data, result);
8622 return result;
8625 /* Expand the one-part VARiable to a location, using the equivalences
8626 in VARS, updating their CUR_LOCs in the process. */
8628 static rtx
8629 vt_expand_1pvar (variable *var, variable_table_type *vars)
8631 struct expand_loc_callback_data data;
8632 rtx loc;
8634 gcc_checking_assert (var->onepart && var->n_var_parts == 1);
8636 if (!dv_changed_p (var->dv))
8637 return var->var_part[0].cur_loc;
8639 INIT_ELCD (data, vars);
8641 loc = vt_expand_var_loc_chain (var, scratch_regs, &data, NULL);
8643 gcc_checking_assert (data.expanding.is_empty ());
8645 FINI_ELCD (data, loc);
8647 return loc;
8650 /* Emit the NOTE_INSN_VAR_LOCATION for variable *VARP. DATA contains
8651 additional parameters: WHERE specifies whether the note shall be emitted
8652 before or after instruction INSN. */
8655 emit_note_insn_var_location (variable **varp, emit_note_data *data)
8657 variable *var = *varp;
8658 rtx_insn *insn = data->insn;
8659 enum emit_note_where where = data->where;
8660 variable_table_type *vars = data->vars;
8661 rtx_note *note;
8662 rtx note_vl;
8663 int i, j, n_var_parts;
8664 bool complete;
8665 enum var_init_status initialized = VAR_INIT_STATUS_UNINITIALIZED;
8666 HOST_WIDE_INT last_limit;
8667 HOST_WIDE_INT offsets[MAX_VAR_PARTS];
8668 rtx loc[MAX_VAR_PARTS];
8669 tree decl;
8670 location_chain *lc;
8672 gcc_checking_assert (var->onepart == NOT_ONEPART
8673 || var->onepart == ONEPART_VDECL);
8675 decl = dv_as_decl (var->dv);
8677 complete = true;
8678 last_limit = 0;
8679 n_var_parts = 0;
8680 if (!var->onepart)
8681 for (i = 0; i < var->n_var_parts; i++)
8682 if (var->var_part[i].cur_loc == NULL && var->var_part[i].loc_chain)
8683 var->var_part[i].cur_loc = var->var_part[i].loc_chain->loc;
8684 for (i = 0; i < var->n_var_parts; i++)
8686 machine_mode mode, wider_mode;
8687 rtx loc2;
8688 HOST_WIDE_INT offset, size, wider_size;
8690 if (i == 0 && var->onepart)
8692 gcc_checking_assert (var->n_var_parts == 1);
8693 offset = 0;
8694 initialized = VAR_INIT_STATUS_INITIALIZED;
8695 loc2 = vt_expand_1pvar (var, vars);
8697 else
8699 if (last_limit < VAR_PART_OFFSET (var, i))
8701 complete = false;
8702 break;
8704 else if (last_limit > VAR_PART_OFFSET (var, i))
8705 continue;
8706 offset = VAR_PART_OFFSET (var, i);
8707 loc2 = var->var_part[i].cur_loc;
8708 if (loc2 && GET_CODE (loc2) == MEM
8709 && GET_CODE (XEXP (loc2, 0)) == VALUE)
8711 rtx depval = XEXP (loc2, 0);
8713 loc2 = vt_expand_loc (loc2, vars);
8715 if (loc2)
8716 loc_exp_insert_dep (var, depval, vars);
8718 if (!loc2)
8720 complete = false;
8721 continue;
8723 gcc_checking_assert (GET_CODE (loc2) != VALUE);
8724 for (lc = var->var_part[i].loc_chain; lc; lc = lc->next)
8725 if (var->var_part[i].cur_loc == lc->loc)
8727 initialized = lc->init;
8728 break;
8730 gcc_assert (lc);
8733 offsets[n_var_parts] = offset;
8734 if (!loc2)
8736 complete = false;
8737 continue;
8739 loc[n_var_parts] = loc2;
8740 mode = GET_MODE (var->var_part[i].cur_loc);
8741 if (mode == VOIDmode && var->onepart)
8742 mode = DECL_MODE (decl);
8743 /* We ony track subparts of constant-sized objects, since at present
8744 there's no representation for polynomial pieces. */
8745 if (!GET_MODE_SIZE (mode).is_constant (&size))
8747 complete = false;
8748 continue;
8750 last_limit = offsets[n_var_parts] + size;
8752 /* Attempt to merge adjacent registers or memory. */
8753 for (j = i + 1; j < var->n_var_parts; j++)
8754 if (last_limit <= VAR_PART_OFFSET (var, j))
8755 break;
8756 if (j < var->n_var_parts
8757 && GET_MODE_WIDER_MODE (mode).exists (&wider_mode)
8758 && GET_MODE_SIZE (wider_mode).is_constant (&wider_size)
8759 && var->var_part[j].cur_loc
8760 && mode == GET_MODE (var->var_part[j].cur_loc)
8761 && (REG_P (loc[n_var_parts]) || MEM_P (loc[n_var_parts]))
8762 && last_limit == (var->onepart ? 0 : VAR_PART_OFFSET (var, j))
8763 && (loc2 = vt_expand_loc (var->var_part[j].cur_loc, vars))
8764 && GET_CODE (loc[n_var_parts]) == GET_CODE (loc2))
8766 rtx new_loc = NULL;
8767 poly_int64 offset2;
8769 if (REG_P (loc[n_var_parts])
8770 && hard_regno_nregs (REGNO (loc[n_var_parts]), mode) * 2
8771 == hard_regno_nregs (REGNO (loc[n_var_parts]), wider_mode)
8772 && end_hard_regno (mode, REGNO (loc[n_var_parts]))
8773 == REGNO (loc2))
8775 if (! WORDS_BIG_ENDIAN && ! BYTES_BIG_ENDIAN)
8776 new_loc = simplify_subreg (wider_mode, loc[n_var_parts],
8777 mode, 0);
8778 else if (WORDS_BIG_ENDIAN && BYTES_BIG_ENDIAN)
8779 new_loc = simplify_subreg (wider_mode, loc2, mode, 0);
8780 if (new_loc)
8782 if (!REG_P (new_loc)
8783 || REGNO (new_loc) != REGNO (loc[n_var_parts]))
8784 new_loc = NULL;
8785 else
8786 REG_ATTRS (new_loc) = REG_ATTRS (loc[n_var_parts]);
8789 else if (MEM_P (loc[n_var_parts])
8790 && GET_CODE (XEXP (loc2, 0)) == PLUS
8791 && REG_P (XEXP (XEXP (loc2, 0), 0))
8792 && poly_int_rtx_p (XEXP (XEXP (loc2, 0), 1), &offset2))
8794 poly_int64 end1 = size;
8795 rtx base1 = strip_offset_and_add (XEXP (loc[n_var_parts], 0),
8796 &end1);
8797 if (rtx_equal_p (base1, XEXP (XEXP (loc2, 0), 0))
8798 && known_eq (end1, offset2))
8799 new_loc = adjust_address_nv (loc[n_var_parts],
8800 wider_mode, 0);
8803 if (new_loc)
8805 loc[n_var_parts] = new_loc;
8806 mode = wider_mode;
8807 last_limit = offsets[n_var_parts] + wider_size;
8808 i = j;
8811 ++n_var_parts;
8813 poly_uint64 type_size_unit
8814 = tree_to_poly_uint64 (TYPE_SIZE_UNIT (TREE_TYPE (decl)));
8815 if (maybe_lt (poly_uint64 (last_limit), type_size_unit))
8816 complete = false;
8818 if (! flag_var_tracking_uninit)
8819 initialized = VAR_INIT_STATUS_INITIALIZED;
8821 note_vl = NULL_RTX;
8822 if (!complete)
8823 note_vl = gen_rtx_VAR_LOCATION (VOIDmode, decl, NULL_RTX, initialized);
8824 else if (n_var_parts == 1)
8826 rtx expr_list;
8828 if (offsets[0] || GET_CODE (loc[0]) == PARALLEL)
8829 expr_list = gen_rtx_EXPR_LIST (VOIDmode, loc[0], GEN_INT (offsets[0]));
8830 else
8831 expr_list = loc[0];
8833 note_vl = gen_rtx_VAR_LOCATION (VOIDmode, decl, expr_list, initialized);
8835 else if (n_var_parts)
8837 rtx parallel;
8839 for (i = 0; i < n_var_parts; i++)
8840 loc[i]
8841 = gen_rtx_EXPR_LIST (VOIDmode, loc[i], GEN_INT (offsets[i]));
8843 parallel = gen_rtx_PARALLEL (VOIDmode,
8844 gen_rtvec_v (n_var_parts, loc));
8845 note_vl = gen_rtx_VAR_LOCATION (VOIDmode, decl,
8846 parallel, initialized);
8849 if (where != EMIT_NOTE_BEFORE_INSN)
8851 note = emit_note_after (NOTE_INSN_VAR_LOCATION, insn);
8852 if (where == EMIT_NOTE_AFTER_CALL_INSN)
8853 NOTE_DURING_CALL_P (note) = true;
8855 else
8857 /* Make sure that the call related notes come first. */
8858 while (NEXT_INSN (insn)
8859 && NOTE_P (insn)
8860 && NOTE_KIND (insn) == NOTE_INSN_VAR_LOCATION
8861 && NOTE_DURING_CALL_P (insn))
8862 insn = NEXT_INSN (insn);
8863 if (NOTE_P (insn)
8864 && NOTE_KIND (insn) == NOTE_INSN_VAR_LOCATION
8865 && NOTE_DURING_CALL_P (insn))
8866 note = emit_note_after (NOTE_INSN_VAR_LOCATION, insn);
8867 else
8868 note = emit_note_before (NOTE_INSN_VAR_LOCATION, insn);
8870 NOTE_VAR_LOCATION (note) = note_vl;
8872 set_dv_changed (var->dv, false);
8873 gcc_assert (var->in_changed_variables);
8874 var->in_changed_variables = false;
8875 changed_variables->clear_slot (varp);
8877 /* Continue traversing the hash table. */
8878 return 1;
8881 /* While traversing changed_variables, push onto DATA (a stack of RTX
8882 values) entries that aren't user variables. */
8885 var_track_values_to_stack (variable **slot,
8886 vec<rtx, va_heap> *changed_values_stack)
8888 variable *var = *slot;
8890 if (var->onepart == ONEPART_VALUE)
8891 changed_values_stack->safe_push (dv_as_value (var->dv));
8892 else if (var->onepart == ONEPART_DEXPR)
8893 changed_values_stack->safe_push (DECL_RTL_KNOWN_SET (dv_as_decl (var->dv)));
8895 return 1;
8898 /* Remove from changed_variables the entry whose DV corresponds to
8899 value or debug_expr VAL. */
8900 static void
8901 remove_value_from_changed_variables (rtx val)
8903 decl_or_value dv = dv_from_rtx (val);
8904 variable **slot;
8905 variable *var;
8907 slot = changed_variables->find_slot_with_hash (dv, dv_htab_hash (dv),
8908 NO_INSERT);
8909 var = *slot;
8910 var->in_changed_variables = false;
8911 changed_variables->clear_slot (slot);
8914 /* If VAL (a value or debug_expr) has backlinks to variables actively
8915 dependent on it in HTAB or in CHANGED_VARIABLES, mark them as
8916 changed, adding to CHANGED_VALUES_STACK any dependencies that may
8917 have dependencies of their own to notify. */
8919 static void
8920 notify_dependents_of_changed_value (rtx val, variable_table_type *htab,
8921 vec<rtx, va_heap> *changed_values_stack)
8923 variable **slot;
8924 variable *var;
8925 loc_exp_dep *led;
8926 decl_or_value dv = dv_from_rtx (val);
8928 slot = changed_variables->find_slot_with_hash (dv, dv_htab_hash (dv),
8929 NO_INSERT);
8930 if (!slot)
8931 slot = htab->find_slot_with_hash (dv, dv_htab_hash (dv), NO_INSERT);
8932 if (!slot)
8933 slot = dropped_values->find_slot_with_hash (dv, dv_htab_hash (dv),
8934 NO_INSERT);
8935 var = *slot;
8937 while ((led = VAR_LOC_DEP_LST (var)))
8939 decl_or_value ldv = led->dv;
8940 variable *ivar;
8942 /* Deactivate and remove the backlink, as it was “used up”. It
8943 makes no sense to attempt to notify the same entity again:
8944 either it will be recomputed and re-register an active
8945 dependency, or it will still have the changed mark. */
8946 if (led->next)
8947 led->next->pprev = led->pprev;
8948 if (led->pprev)
8949 *led->pprev = led->next;
8950 led->next = NULL;
8951 led->pprev = NULL;
8953 if (dv_changed_p (ldv))
8954 continue;
8956 switch (dv_onepart_p (ldv))
8958 case ONEPART_VALUE:
8959 case ONEPART_DEXPR:
8960 set_dv_changed (ldv, true);
8961 changed_values_stack->safe_push (dv_as_rtx (ldv));
8962 break;
8964 case ONEPART_VDECL:
8965 ivar = htab->find_with_hash (ldv, dv_htab_hash (ldv));
8966 gcc_checking_assert (!VAR_LOC_DEP_LST (ivar));
8967 variable_was_changed (ivar, NULL);
8968 break;
8970 case NOT_ONEPART:
8971 delete led;
8972 ivar = htab->find_with_hash (ldv, dv_htab_hash (ldv));
8973 if (ivar)
8975 int i = ivar->n_var_parts;
8976 while (i--)
8978 rtx loc = ivar->var_part[i].cur_loc;
8980 if (loc && GET_CODE (loc) == MEM
8981 && XEXP (loc, 0) == val)
8983 variable_was_changed (ivar, NULL);
8984 break;
8988 break;
8990 default:
8991 gcc_unreachable ();
8996 /* Take out of changed_variables any entries that don't refer to use
8997 variables. Back-propagate change notifications from values and
8998 debug_exprs to their active dependencies in HTAB or in
8999 CHANGED_VARIABLES. */
9001 static void
9002 process_changed_values (variable_table_type *htab)
9004 int i, n;
9005 rtx val;
9006 auto_vec<rtx, 20> changed_values_stack;
9008 /* Move values from changed_variables to changed_values_stack. */
9009 changed_variables
9010 ->traverse <vec<rtx, va_heap>*, var_track_values_to_stack>
9011 (&changed_values_stack);
9013 /* Back-propagate change notifications in values while popping
9014 them from the stack. */
9015 for (n = i = changed_values_stack.length ();
9016 i > 0; i = changed_values_stack.length ())
9018 val = changed_values_stack.pop ();
9019 notify_dependents_of_changed_value (val, htab, &changed_values_stack);
9021 /* This condition will hold when visiting each of the entries
9022 originally in changed_variables. We can't remove them
9023 earlier because this could drop the backlinks before we got a
9024 chance to use them. */
9025 if (i == n)
9027 remove_value_from_changed_variables (val);
9028 n--;
9033 /* Emit NOTE_INSN_VAR_LOCATION note for each variable from a chain
9034 CHANGED_VARIABLES and delete this chain. WHERE specifies whether
9035 the notes shall be emitted before of after instruction INSN. */
9037 static void
9038 emit_notes_for_changes (rtx_insn *insn, enum emit_note_where where,
9039 shared_hash *vars)
9041 emit_note_data data;
9042 variable_table_type *htab = shared_hash_htab (vars);
9044 if (!changed_variables->elements ())
9045 return;
9047 if (MAY_HAVE_DEBUG_BIND_INSNS)
9048 process_changed_values (htab);
9050 data.insn = insn;
9051 data.where = where;
9052 data.vars = htab;
9054 changed_variables
9055 ->traverse <emit_note_data*, emit_note_insn_var_location> (&data);
9058 /* Add variable *SLOT to the chain CHANGED_VARIABLES if it differs from the
9059 same variable in hash table DATA or is not there at all. */
9062 emit_notes_for_differences_1 (variable **slot, variable_table_type *new_vars)
9064 variable *old_var, *new_var;
9066 old_var = *slot;
9067 new_var = new_vars->find_with_hash (old_var->dv, dv_htab_hash (old_var->dv));
9069 if (!new_var)
9071 /* Variable has disappeared. */
9072 variable *empty_var = NULL;
9074 if (old_var->onepart == ONEPART_VALUE
9075 || old_var->onepart == ONEPART_DEXPR)
9077 empty_var = variable_from_dropped (old_var->dv, NO_INSERT);
9078 if (empty_var)
9080 gcc_checking_assert (!empty_var->in_changed_variables);
9081 if (!VAR_LOC_1PAUX (old_var))
9083 VAR_LOC_1PAUX (old_var) = VAR_LOC_1PAUX (empty_var);
9084 VAR_LOC_1PAUX (empty_var) = NULL;
9086 else
9087 gcc_checking_assert (!VAR_LOC_1PAUX (empty_var));
9091 if (!empty_var)
9093 empty_var = onepart_pool_allocate (old_var->onepart);
9094 empty_var->dv = old_var->dv;
9095 empty_var->refcount = 0;
9096 empty_var->n_var_parts = 0;
9097 empty_var->onepart = old_var->onepart;
9098 empty_var->in_changed_variables = false;
9101 if (empty_var->onepart)
9103 /* Propagate the auxiliary data to (ultimately)
9104 changed_variables. */
9105 empty_var->var_part[0].loc_chain = NULL;
9106 empty_var->var_part[0].cur_loc = NULL;
9107 VAR_LOC_1PAUX (empty_var) = VAR_LOC_1PAUX (old_var);
9108 VAR_LOC_1PAUX (old_var) = NULL;
9110 variable_was_changed (empty_var, NULL);
9111 /* Continue traversing the hash table. */
9112 return 1;
9114 /* Update cur_loc and one-part auxiliary data, before new_var goes
9115 through variable_was_changed. */
9116 if (old_var != new_var && new_var->onepart)
9118 gcc_checking_assert (VAR_LOC_1PAUX (new_var) == NULL);
9119 VAR_LOC_1PAUX (new_var) = VAR_LOC_1PAUX (old_var);
9120 VAR_LOC_1PAUX (old_var) = NULL;
9121 new_var->var_part[0].cur_loc = old_var->var_part[0].cur_loc;
9123 if (variable_different_p (old_var, new_var))
9124 variable_was_changed (new_var, NULL);
9126 /* Continue traversing the hash table. */
9127 return 1;
9130 /* Add variable *SLOT to the chain CHANGED_VARIABLES if it is not in hash
9131 table DATA. */
9134 emit_notes_for_differences_2 (variable **slot, variable_table_type *old_vars)
9136 variable *old_var, *new_var;
9138 new_var = *slot;
9139 old_var = old_vars->find_with_hash (new_var->dv, dv_htab_hash (new_var->dv));
9140 if (!old_var)
9142 int i;
9143 for (i = 0; i < new_var->n_var_parts; i++)
9144 new_var->var_part[i].cur_loc = NULL;
9145 variable_was_changed (new_var, NULL);
9148 /* Continue traversing the hash table. */
9149 return 1;
9152 /* Emit notes before INSN for differences between dataflow sets OLD_SET and
9153 NEW_SET. */
9155 static void
9156 emit_notes_for_differences (rtx_insn *insn, dataflow_set *old_set,
9157 dataflow_set *new_set)
9159 shared_hash_htab (old_set->vars)
9160 ->traverse <variable_table_type *, emit_notes_for_differences_1>
9161 (shared_hash_htab (new_set->vars));
9162 shared_hash_htab (new_set->vars)
9163 ->traverse <variable_table_type *, emit_notes_for_differences_2>
9164 (shared_hash_htab (old_set->vars));
9165 emit_notes_for_changes (insn, EMIT_NOTE_BEFORE_INSN, new_set->vars);
9168 /* Return the next insn after INSN that is not a NOTE_INSN_VAR_LOCATION. */
9170 static rtx_insn *
9171 next_non_note_insn_var_location (rtx_insn *insn)
9173 while (insn)
9175 insn = NEXT_INSN (insn);
9176 if (insn == 0
9177 || !NOTE_P (insn)
9178 || NOTE_KIND (insn) != NOTE_INSN_VAR_LOCATION)
9179 break;
9182 return insn;
9185 /* Emit the notes for changes of location parts in the basic block BB. */
9187 static void
9188 emit_notes_in_bb (basic_block bb, dataflow_set *set)
9190 unsigned int i;
9191 micro_operation *mo;
9193 dataflow_set_clear (set);
9194 dataflow_set_copy (set, &VTI (bb)->in);
9196 FOR_EACH_VEC_ELT (VTI (bb)->mos, i, mo)
9198 rtx_insn *insn = mo->insn;
9199 rtx_insn *next_insn = next_non_note_insn_var_location (insn);
9201 switch (mo->type)
9203 case MO_CALL:
9204 dataflow_set_clear_at_call (set, insn);
9205 emit_notes_for_changes (insn, EMIT_NOTE_AFTER_CALL_INSN, set->vars);
9207 rtx arguments = mo->u.loc, *p = &arguments;
9208 while (*p)
9210 XEXP (XEXP (*p, 0), 1)
9211 = vt_expand_loc (XEXP (XEXP (*p, 0), 1),
9212 shared_hash_htab (set->vars));
9213 /* If expansion is successful, keep it in the list. */
9214 if (XEXP (XEXP (*p, 0), 1))
9216 XEXP (XEXP (*p, 0), 1)
9217 = copy_rtx_if_shared (XEXP (XEXP (*p, 0), 1));
9218 p = &XEXP (*p, 1);
9220 /* Otherwise, if the following item is data_value for it,
9221 drop it too too. */
9222 else if (XEXP (*p, 1)
9223 && REG_P (XEXP (XEXP (*p, 0), 0))
9224 && MEM_P (XEXP (XEXP (XEXP (*p, 1), 0), 0))
9225 && REG_P (XEXP (XEXP (XEXP (XEXP (*p, 1), 0), 0),
9227 && REGNO (XEXP (XEXP (*p, 0), 0))
9228 == REGNO (XEXP (XEXP (XEXP (XEXP (*p, 1), 0),
9229 0), 0)))
9230 *p = XEXP (XEXP (*p, 1), 1);
9231 /* Just drop this item. */
9232 else
9233 *p = XEXP (*p, 1);
9235 add_reg_note (insn, REG_CALL_ARG_LOCATION, arguments);
9237 break;
9239 case MO_USE:
9241 rtx loc = mo->u.loc;
9243 if (REG_P (loc))
9244 var_reg_set (set, loc, VAR_INIT_STATUS_UNINITIALIZED, NULL);
9245 else
9246 var_mem_set (set, loc, VAR_INIT_STATUS_UNINITIALIZED, NULL);
9248 emit_notes_for_changes (insn, EMIT_NOTE_BEFORE_INSN, set->vars);
9250 break;
9252 case MO_VAL_LOC:
9254 rtx loc = mo->u.loc;
9255 rtx val, vloc;
9256 tree var;
9258 if (GET_CODE (loc) == CONCAT)
9260 val = XEXP (loc, 0);
9261 vloc = XEXP (loc, 1);
9263 else
9265 val = NULL_RTX;
9266 vloc = loc;
9269 var = PAT_VAR_LOCATION_DECL (vloc);
9271 clobber_variable_part (set, NULL_RTX,
9272 dv_from_decl (var), 0, NULL_RTX);
9273 if (val)
9275 if (VAL_NEEDS_RESOLUTION (loc))
9276 val_resolve (set, val, PAT_VAR_LOCATION_LOC (vloc), insn);
9277 set_variable_part (set, val, dv_from_decl (var), 0,
9278 VAR_INIT_STATUS_INITIALIZED, NULL_RTX,
9279 INSERT);
9281 else if (!VAR_LOC_UNKNOWN_P (PAT_VAR_LOCATION_LOC (vloc)))
9282 set_variable_part (set, PAT_VAR_LOCATION_LOC (vloc),
9283 dv_from_decl (var), 0,
9284 VAR_INIT_STATUS_INITIALIZED, NULL_RTX,
9285 INSERT);
9287 emit_notes_for_changes (insn, EMIT_NOTE_AFTER_INSN, set->vars);
9289 break;
9291 case MO_VAL_USE:
9293 rtx loc = mo->u.loc;
9294 rtx val, vloc, uloc;
9296 vloc = uloc = XEXP (loc, 1);
9297 val = XEXP (loc, 0);
9299 if (GET_CODE (val) == CONCAT)
9301 uloc = XEXP (val, 1);
9302 val = XEXP (val, 0);
9305 if (VAL_NEEDS_RESOLUTION (loc))
9306 val_resolve (set, val, vloc, insn);
9307 else
9308 val_store (set, val, uloc, insn, false);
9310 if (VAL_HOLDS_TRACK_EXPR (loc))
9312 if (GET_CODE (uloc) == REG)
9313 var_reg_set (set, uloc, VAR_INIT_STATUS_UNINITIALIZED,
9314 NULL);
9315 else if (GET_CODE (uloc) == MEM)
9316 var_mem_set (set, uloc, VAR_INIT_STATUS_UNINITIALIZED,
9317 NULL);
9320 emit_notes_for_changes (insn, EMIT_NOTE_BEFORE_INSN, set->vars);
9322 break;
9324 case MO_VAL_SET:
9326 rtx loc = mo->u.loc;
9327 rtx val, vloc, uloc;
9328 rtx dstv, srcv;
9330 vloc = loc;
9331 uloc = XEXP (vloc, 1);
9332 val = XEXP (vloc, 0);
9333 vloc = uloc;
9335 if (GET_CODE (uloc) == SET)
9337 dstv = SET_DEST (uloc);
9338 srcv = SET_SRC (uloc);
9340 else
9342 dstv = uloc;
9343 srcv = NULL;
9346 if (GET_CODE (val) == CONCAT)
9348 dstv = vloc = XEXP (val, 1);
9349 val = XEXP (val, 0);
9352 if (GET_CODE (vloc) == SET)
9354 srcv = SET_SRC (vloc);
9356 gcc_assert (val != srcv);
9357 gcc_assert (vloc == uloc || VAL_NEEDS_RESOLUTION (loc));
9359 dstv = vloc = SET_DEST (vloc);
9361 if (VAL_NEEDS_RESOLUTION (loc))
9362 val_resolve (set, val, srcv, insn);
9364 else if (VAL_NEEDS_RESOLUTION (loc))
9366 gcc_assert (GET_CODE (uloc) == SET
9367 && GET_CODE (SET_SRC (uloc)) == REG);
9368 val_resolve (set, val, SET_SRC (uloc), insn);
9371 if (VAL_HOLDS_TRACK_EXPR (loc))
9373 if (VAL_EXPR_IS_CLOBBERED (loc))
9375 if (REG_P (uloc))
9376 var_reg_delete (set, uloc, true);
9377 else if (MEM_P (uloc))
9379 gcc_assert (MEM_P (dstv));
9380 gcc_assert (MEM_ATTRS (dstv) == MEM_ATTRS (uloc));
9381 var_mem_delete (set, dstv, true);
9384 else
9386 bool copied_p = VAL_EXPR_IS_COPIED (loc);
9387 rtx src = NULL, dst = uloc;
9388 enum var_init_status status = VAR_INIT_STATUS_INITIALIZED;
9390 if (GET_CODE (uloc) == SET)
9392 src = SET_SRC (uloc);
9393 dst = SET_DEST (uloc);
9396 if (copied_p)
9398 status = find_src_status (set, src);
9400 src = find_src_set_src (set, src);
9403 if (REG_P (dst))
9404 var_reg_delete_and_set (set, dst, !copied_p,
9405 status, srcv);
9406 else if (MEM_P (dst))
9408 gcc_assert (MEM_P (dstv));
9409 gcc_assert (MEM_ATTRS (dstv) == MEM_ATTRS (dst));
9410 var_mem_delete_and_set (set, dstv, !copied_p,
9411 status, srcv);
9415 else if (REG_P (uloc))
9416 var_regno_delete (set, REGNO (uloc));
9417 else if (MEM_P (uloc))
9419 gcc_checking_assert (GET_CODE (vloc) == MEM);
9420 gcc_checking_assert (vloc == dstv);
9421 if (vloc != dstv)
9422 clobber_overlapping_mems (set, vloc);
9425 val_store (set, val, dstv, insn, true);
9427 emit_notes_for_changes (next_insn, EMIT_NOTE_BEFORE_INSN,
9428 set->vars);
9430 break;
9432 case MO_SET:
9434 rtx loc = mo->u.loc;
9435 rtx set_src = NULL;
9437 if (GET_CODE (loc) == SET)
9439 set_src = SET_SRC (loc);
9440 loc = SET_DEST (loc);
9443 if (REG_P (loc))
9444 var_reg_delete_and_set (set, loc, true, VAR_INIT_STATUS_INITIALIZED,
9445 set_src);
9446 else
9447 var_mem_delete_and_set (set, loc, true, VAR_INIT_STATUS_INITIALIZED,
9448 set_src);
9450 emit_notes_for_changes (next_insn, EMIT_NOTE_BEFORE_INSN,
9451 set->vars);
9453 break;
9455 case MO_COPY:
9457 rtx loc = mo->u.loc;
9458 enum var_init_status src_status;
9459 rtx set_src = NULL;
9461 if (GET_CODE (loc) == SET)
9463 set_src = SET_SRC (loc);
9464 loc = SET_DEST (loc);
9467 src_status = find_src_status (set, set_src);
9468 set_src = find_src_set_src (set, set_src);
9470 if (REG_P (loc))
9471 var_reg_delete_and_set (set, loc, false, src_status, set_src);
9472 else
9473 var_mem_delete_and_set (set, loc, false, src_status, set_src);
9475 emit_notes_for_changes (next_insn, EMIT_NOTE_BEFORE_INSN,
9476 set->vars);
9478 break;
9480 case MO_USE_NO_VAR:
9482 rtx loc = mo->u.loc;
9484 if (REG_P (loc))
9485 var_reg_delete (set, loc, false);
9486 else
9487 var_mem_delete (set, loc, false);
9489 emit_notes_for_changes (insn, EMIT_NOTE_AFTER_INSN, set->vars);
9491 break;
9493 case MO_CLOBBER:
9495 rtx loc = mo->u.loc;
9497 if (REG_P (loc))
9498 var_reg_delete (set, loc, true);
9499 else
9500 var_mem_delete (set, loc, true);
9502 emit_notes_for_changes (next_insn, EMIT_NOTE_BEFORE_INSN,
9503 set->vars);
9505 break;
9507 case MO_ADJUST:
9508 set->stack_adjust += mo->u.adjust;
9509 break;
9514 /* Emit notes for the whole function. */
9516 static void
9517 vt_emit_notes (void)
9519 basic_block bb;
9520 dataflow_set cur;
9522 gcc_assert (!changed_variables->elements ());
9524 /* Free memory occupied by the out hash tables, as they aren't used
9525 anymore. */
9526 FOR_EACH_BB_FN (bb, cfun)
9527 dataflow_set_clear (&VTI (bb)->out);
9529 /* Enable emitting notes by functions (mainly by set_variable_part and
9530 delete_variable_part). */
9531 emit_notes = true;
9533 if (MAY_HAVE_DEBUG_BIND_INSNS)
9534 dropped_values = new variable_table_type (cselib_get_next_uid () * 2);
9536 dataflow_set_init (&cur);
9538 FOR_EACH_BB_FN (bb, cfun)
9540 /* Emit the notes for changes of variable locations between two
9541 subsequent basic blocks. */
9542 emit_notes_for_differences (BB_HEAD (bb), &cur, &VTI (bb)->in);
9544 if (MAY_HAVE_DEBUG_BIND_INSNS)
9545 local_get_addr_cache = new hash_map<rtx, rtx>;
9547 /* Emit the notes for the changes in the basic block itself. */
9548 emit_notes_in_bb (bb, &cur);
9550 if (MAY_HAVE_DEBUG_BIND_INSNS)
9551 delete local_get_addr_cache;
9552 local_get_addr_cache = NULL;
9554 /* Free memory occupied by the in hash table, we won't need it
9555 again. */
9556 dataflow_set_clear (&VTI (bb)->in);
9559 if (flag_checking)
9560 shared_hash_htab (cur.vars)
9561 ->traverse <variable_table_type *, emit_notes_for_differences_1>
9562 (shared_hash_htab (empty_shared_hash));
9564 dataflow_set_destroy (&cur);
9566 if (MAY_HAVE_DEBUG_BIND_INSNS)
9567 delete dropped_values;
9568 dropped_values = NULL;
9570 emit_notes = false;
9573 /* If there is a declaration and offset associated with register/memory RTL
9574 assign declaration to *DECLP and offset to *OFFSETP, and return true. */
9576 static bool
9577 vt_get_decl_and_offset (rtx rtl, tree *declp, poly_int64 *offsetp)
9579 if (REG_P (rtl))
9581 if (REG_ATTRS (rtl))
9583 *declp = REG_EXPR (rtl);
9584 *offsetp = REG_OFFSET (rtl);
9585 return true;
9588 else if (GET_CODE (rtl) == PARALLEL)
9590 tree decl = NULL_TREE;
9591 HOST_WIDE_INT offset = MAX_VAR_PARTS;
9592 int len = XVECLEN (rtl, 0), i;
9594 for (i = 0; i < len; i++)
9596 rtx reg = XEXP (XVECEXP (rtl, 0, i), 0);
9597 if (!REG_P (reg) || !REG_ATTRS (reg))
9598 break;
9599 if (!decl)
9600 decl = REG_EXPR (reg);
9601 if (REG_EXPR (reg) != decl)
9602 break;
9603 HOST_WIDE_INT this_offset;
9604 if (!track_offset_p (REG_OFFSET (reg), &this_offset))
9605 break;
9606 offset = MIN (offset, this_offset);
9609 if (i == len)
9611 *declp = decl;
9612 *offsetp = offset;
9613 return true;
9616 else if (MEM_P (rtl))
9618 if (MEM_ATTRS (rtl))
9620 *declp = MEM_EXPR (rtl);
9621 *offsetp = int_mem_offset (rtl);
9622 return true;
9625 return false;
9628 /* Record the value for the ENTRY_VALUE of RTL as a global equivalence
9629 of VAL. */
9631 static void
9632 record_entry_value (cselib_val *val, rtx rtl)
9634 rtx ev = gen_rtx_ENTRY_VALUE (GET_MODE (rtl));
9636 ENTRY_VALUE_EXP (ev) = rtl;
9638 cselib_add_permanent_equiv (val, ev, get_insns ());
9641 /* Insert function parameter PARM in IN and OUT sets of ENTRY_BLOCK. */
9643 static void
9644 vt_add_function_parameter (tree parm)
9646 rtx decl_rtl = DECL_RTL_IF_SET (parm);
9647 rtx incoming = DECL_INCOMING_RTL (parm);
9648 tree decl;
9649 machine_mode mode;
9650 poly_int64 offset;
9651 dataflow_set *out;
9652 decl_or_value dv;
9653 bool incoming_ok = true;
9655 if (TREE_CODE (parm) != PARM_DECL)
9656 return;
9658 if (!decl_rtl || !incoming)
9659 return;
9661 if (GET_MODE (decl_rtl) == BLKmode || GET_MODE (incoming) == BLKmode)
9662 return;
9664 /* If there is a DRAP register or a pseudo in internal_arg_pointer,
9665 rewrite the incoming location of parameters passed on the stack
9666 into MEMs based on the argument pointer, so that incoming doesn't
9667 depend on a pseudo. */
9668 poly_int64 incoming_offset = 0;
9669 if (MEM_P (incoming)
9670 && (strip_offset (XEXP (incoming, 0), &incoming_offset)
9671 == crtl->args.internal_arg_pointer))
9673 HOST_WIDE_INT off = -FIRST_PARM_OFFSET (current_function_decl);
9674 incoming
9675 = replace_equiv_address_nv (incoming,
9676 plus_constant (Pmode,
9677 arg_pointer_rtx,
9678 off + incoming_offset));
9681 #ifdef HAVE_window_save
9682 /* DECL_INCOMING_RTL uses the INCOMING_REGNO of parameter registers.
9683 If the target machine has an explicit window save instruction, the
9684 actual entry value is the corresponding OUTGOING_REGNO instead. */
9685 if (HAVE_window_save && !crtl->uses_only_leaf_regs)
9687 if (REG_P (incoming)
9688 && HARD_REGISTER_P (incoming)
9689 && OUTGOING_REGNO (REGNO (incoming)) != REGNO (incoming))
9691 parm_reg p;
9692 p.incoming = incoming;
9693 incoming
9694 = gen_rtx_REG_offset (incoming, GET_MODE (incoming),
9695 OUTGOING_REGNO (REGNO (incoming)), 0);
9696 p.outgoing = incoming;
9697 vec_safe_push (windowed_parm_regs, p);
9699 else if (GET_CODE (incoming) == PARALLEL)
9701 rtx outgoing
9702 = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (XVECLEN (incoming, 0)));
9703 int i;
9705 for (i = 0; i < XVECLEN (incoming, 0); i++)
9707 rtx reg = XEXP (XVECEXP (incoming, 0, i), 0);
9708 parm_reg p;
9709 p.incoming = reg;
9710 reg = gen_rtx_REG_offset (reg, GET_MODE (reg),
9711 OUTGOING_REGNO (REGNO (reg)), 0);
9712 p.outgoing = reg;
9713 XVECEXP (outgoing, 0, i)
9714 = gen_rtx_EXPR_LIST (VOIDmode, reg,
9715 XEXP (XVECEXP (incoming, 0, i), 1));
9716 vec_safe_push (windowed_parm_regs, p);
9719 incoming = outgoing;
9721 else if (MEM_P (incoming)
9722 && REG_P (XEXP (incoming, 0))
9723 && HARD_REGISTER_P (XEXP (incoming, 0)))
9725 rtx reg = XEXP (incoming, 0);
9726 if (OUTGOING_REGNO (REGNO (reg)) != REGNO (reg))
9728 parm_reg p;
9729 p.incoming = reg;
9730 reg = gen_raw_REG (GET_MODE (reg), OUTGOING_REGNO (REGNO (reg)));
9731 p.outgoing = reg;
9732 vec_safe_push (windowed_parm_regs, p);
9733 incoming = replace_equiv_address_nv (incoming, reg);
9737 #endif
9739 if (!vt_get_decl_and_offset (incoming, &decl, &offset))
9741 incoming_ok = false;
9742 if (MEM_P (incoming))
9744 /* This means argument is passed by invisible reference. */
9745 offset = 0;
9746 decl = parm;
9748 else
9750 if (!vt_get_decl_and_offset (decl_rtl, &decl, &offset))
9751 return;
9752 offset += byte_lowpart_offset (GET_MODE (incoming),
9753 GET_MODE (decl_rtl));
9757 if (!decl)
9758 return;
9760 if (parm != decl)
9762 /* If that DECL_RTL wasn't a pseudo that got spilled to
9763 memory, bail out. Otherwise, the spill slot sharing code
9764 will force the memory to reference spill_slot_decl (%sfp),
9765 so we don't match above. That's ok, the pseudo must have
9766 referenced the entire parameter, so just reset OFFSET. */
9767 if (decl != get_spill_slot_decl (false))
9768 return;
9769 offset = 0;
9772 HOST_WIDE_INT const_offset;
9773 if (!track_loc_p (incoming, parm, offset, false, &mode, &const_offset))
9774 return;
9776 out = &VTI (ENTRY_BLOCK_PTR_FOR_FN (cfun))->out;
9778 dv = dv_from_decl (parm);
9780 if (target_for_debug_bind (parm)
9781 /* We can't deal with these right now, because this kind of
9782 variable is single-part. ??? We could handle parallels
9783 that describe multiple locations for the same single
9784 value, but ATM we don't. */
9785 && GET_CODE (incoming) != PARALLEL)
9787 cselib_val *val;
9788 rtx lowpart;
9790 /* ??? We shouldn't ever hit this, but it may happen because
9791 arguments passed by invisible reference aren't dealt with
9792 above: incoming-rtl will have Pmode rather than the
9793 expected mode for the type. */
9794 if (const_offset)
9795 return;
9797 lowpart = var_lowpart (mode, incoming);
9798 if (!lowpart)
9799 return;
9801 val = cselib_lookup_from_insn (lowpart, mode, true,
9802 VOIDmode, get_insns ());
9804 /* ??? Float-typed values in memory are not handled by
9805 cselib. */
9806 if (val)
9808 preserve_value (val);
9809 set_variable_part (out, val->val_rtx, dv, const_offset,
9810 VAR_INIT_STATUS_INITIALIZED, NULL, INSERT);
9811 dv = dv_from_value (val->val_rtx);
9814 if (MEM_P (incoming))
9816 val = cselib_lookup_from_insn (XEXP (incoming, 0), mode, true,
9817 VOIDmode, get_insns ());
9818 if (val)
9820 preserve_value (val);
9821 incoming = replace_equiv_address_nv (incoming, val->val_rtx);
9826 if (REG_P (incoming))
9828 incoming = var_lowpart (mode, incoming);
9829 gcc_assert (REGNO (incoming) < FIRST_PSEUDO_REGISTER);
9830 attrs_list_insert (&out->regs[REGNO (incoming)], dv, const_offset,
9831 incoming);
9832 set_variable_part (out, incoming, dv, const_offset,
9833 VAR_INIT_STATUS_INITIALIZED, NULL, INSERT);
9834 if (dv_is_value_p (dv))
9836 record_entry_value (CSELIB_VAL_PTR (dv_as_value (dv)), incoming);
9837 if (TREE_CODE (TREE_TYPE (parm)) == REFERENCE_TYPE
9838 && INTEGRAL_TYPE_P (TREE_TYPE (TREE_TYPE (parm))))
9840 machine_mode indmode
9841 = TYPE_MODE (TREE_TYPE (TREE_TYPE (parm)));
9842 rtx mem = gen_rtx_MEM (indmode, incoming);
9843 cselib_val *val = cselib_lookup_from_insn (mem, indmode, true,
9844 VOIDmode,
9845 get_insns ());
9846 if (val)
9848 preserve_value (val);
9849 record_entry_value (val, mem);
9850 set_variable_part (out, mem, dv_from_value (val->val_rtx), 0,
9851 VAR_INIT_STATUS_INITIALIZED, NULL, INSERT);
9856 else if (GET_CODE (incoming) == PARALLEL && !dv_onepart_p (dv))
9858 int i;
9860 /* The following code relies on vt_get_decl_and_offset returning true for
9861 incoming, which might not be always the case. */
9862 if (!incoming_ok)
9863 return;
9864 for (i = 0; i < XVECLEN (incoming, 0); i++)
9866 rtx reg = XEXP (XVECEXP (incoming, 0, i), 0);
9867 /* vt_get_decl_and_offset has already checked that the offset
9868 is a valid variable part. */
9869 const_offset = get_tracked_reg_offset (reg);
9870 gcc_assert (REGNO (reg) < FIRST_PSEUDO_REGISTER);
9871 attrs_list_insert (&out->regs[REGNO (reg)], dv, const_offset, reg);
9872 set_variable_part (out, reg, dv, const_offset,
9873 VAR_INIT_STATUS_INITIALIZED, NULL, INSERT);
9876 else if (MEM_P (incoming))
9878 incoming = var_lowpart (mode, incoming);
9879 set_variable_part (out, incoming, dv, const_offset,
9880 VAR_INIT_STATUS_INITIALIZED, NULL, INSERT);
9884 /* Insert function parameters to IN and OUT sets of ENTRY_BLOCK. */
9886 static void
9887 vt_add_function_parameters (void)
9889 tree parm;
9891 for (parm = DECL_ARGUMENTS (current_function_decl);
9892 parm; parm = DECL_CHAIN (parm))
9893 vt_add_function_parameter (parm);
9895 if (DECL_HAS_VALUE_EXPR_P (DECL_RESULT (current_function_decl)))
9897 tree vexpr = DECL_VALUE_EXPR (DECL_RESULT (current_function_decl));
9899 if (TREE_CODE (vexpr) == INDIRECT_REF)
9900 vexpr = TREE_OPERAND (vexpr, 0);
9902 if (TREE_CODE (vexpr) == PARM_DECL
9903 && DECL_ARTIFICIAL (vexpr)
9904 && !DECL_IGNORED_P (vexpr)
9905 && DECL_NAMELESS (vexpr))
9906 vt_add_function_parameter (vexpr);
9910 /* Initialize cfa_base_rtx, create a preserved VALUE for it and
9911 ensure it isn't flushed during cselib_reset_table.
9912 Can be called only if frame_pointer_rtx resp. arg_pointer_rtx
9913 has been eliminated. */
9915 static void
9916 vt_init_cfa_base (void)
9918 cselib_val *val;
9920 #ifdef FRAME_POINTER_CFA_OFFSET
9921 cfa_base_rtx = frame_pointer_rtx;
9922 cfa_base_offset = -FRAME_POINTER_CFA_OFFSET (current_function_decl);
9923 #else
9924 cfa_base_rtx = arg_pointer_rtx;
9925 cfa_base_offset = -ARG_POINTER_CFA_OFFSET (current_function_decl);
9926 #endif
9927 if (cfa_base_rtx == hard_frame_pointer_rtx
9928 || !fixed_regs[REGNO (cfa_base_rtx)])
9930 cfa_base_rtx = NULL_RTX;
9931 return;
9933 if (!MAY_HAVE_DEBUG_BIND_INSNS)
9934 return;
9936 /* Tell alias analysis that cfa_base_rtx should share
9937 find_base_term value with stack pointer or hard frame pointer. */
9938 if (!frame_pointer_needed)
9939 vt_equate_reg_base_value (cfa_base_rtx, stack_pointer_rtx);
9940 else if (!crtl->stack_realign_tried)
9941 vt_equate_reg_base_value (cfa_base_rtx, hard_frame_pointer_rtx);
9943 val = cselib_lookup_from_insn (cfa_base_rtx, GET_MODE (cfa_base_rtx), 1,
9944 VOIDmode, get_insns ());
9945 preserve_value (val);
9946 cselib_preserve_cfa_base_value (val, REGNO (cfa_base_rtx));
9949 /* Reemit INSN, a MARKER_DEBUG_INSN, as a note. */
9951 static rtx_insn *
9952 reemit_marker_as_note (rtx_insn *insn)
9954 gcc_checking_assert (DEBUG_MARKER_INSN_P (insn));
9956 enum insn_note kind = INSN_DEBUG_MARKER_KIND (insn);
9958 switch (kind)
9960 case NOTE_INSN_BEGIN_STMT:
9961 case NOTE_INSN_INLINE_ENTRY:
9963 rtx_insn *note = NULL;
9964 if (cfun->debug_nonbind_markers)
9966 note = emit_note_before (kind, insn);
9967 NOTE_MARKER_LOCATION (note) = INSN_LOCATION (insn);
9969 delete_insn (insn);
9970 return note;
9973 default:
9974 gcc_unreachable ();
9978 /* Allocate and initialize the data structures for variable tracking
9979 and parse the RTL to get the micro operations. */
9981 static bool
9982 vt_initialize (void)
9984 basic_block bb;
9985 poly_int64 fp_cfa_offset = -1;
9987 alloc_aux_for_blocks (sizeof (variable_tracking_info));
9989 empty_shared_hash = shared_hash_pool.allocate ();
9990 empty_shared_hash->refcount = 1;
9991 empty_shared_hash->htab = new variable_table_type (1);
9992 changed_variables = new variable_table_type (10);
9994 /* Init the IN and OUT sets. */
9995 FOR_ALL_BB_FN (bb, cfun)
9997 VTI (bb)->visited = false;
9998 VTI (bb)->flooded = false;
9999 dataflow_set_init (&VTI (bb)->in);
10000 dataflow_set_init (&VTI (bb)->out);
10001 VTI (bb)->permp = NULL;
10004 if (MAY_HAVE_DEBUG_BIND_INSNS)
10006 cselib_init (CSELIB_RECORD_MEMORY | CSELIB_PRESERVE_CONSTANTS);
10007 scratch_regs = BITMAP_ALLOC (NULL);
10008 preserved_values.create (256);
10009 global_get_addr_cache = new hash_map<rtx, rtx>;
10011 else
10013 scratch_regs = NULL;
10014 global_get_addr_cache = NULL;
10017 if (MAY_HAVE_DEBUG_BIND_INSNS)
10019 rtx reg, expr;
10020 int ofst;
10021 cselib_val *val;
10023 #ifdef FRAME_POINTER_CFA_OFFSET
10024 reg = frame_pointer_rtx;
10025 ofst = FRAME_POINTER_CFA_OFFSET (current_function_decl);
10026 #else
10027 reg = arg_pointer_rtx;
10028 ofst = ARG_POINTER_CFA_OFFSET (current_function_decl);
10029 #endif
10031 ofst -= INCOMING_FRAME_SP_OFFSET;
10033 val = cselib_lookup_from_insn (reg, GET_MODE (reg), 1,
10034 VOIDmode, get_insns ());
10035 preserve_value (val);
10036 if (reg != hard_frame_pointer_rtx && fixed_regs[REGNO (reg)])
10037 cselib_preserve_cfa_base_value (val, REGNO (reg));
10038 expr = plus_constant (GET_MODE (stack_pointer_rtx),
10039 stack_pointer_rtx, -ofst);
10040 cselib_add_permanent_equiv (val, expr, get_insns ());
10042 if (ofst)
10044 val = cselib_lookup_from_insn (stack_pointer_rtx,
10045 GET_MODE (stack_pointer_rtx), 1,
10046 VOIDmode, get_insns ());
10047 preserve_value (val);
10048 expr = plus_constant (GET_MODE (reg), reg, ofst);
10049 cselib_add_permanent_equiv (val, expr, get_insns ());
10053 /* In order to factor out the adjustments made to the stack pointer or to
10054 the hard frame pointer and thus be able to use DW_OP_fbreg operations
10055 instead of individual location lists, we're going to rewrite MEMs based
10056 on them into MEMs based on the CFA by de-eliminating stack_pointer_rtx
10057 or hard_frame_pointer_rtx to the virtual CFA pointer frame_pointer_rtx
10058 resp. arg_pointer_rtx. We can do this either when there is no frame
10059 pointer in the function and stack adjustments are consistent for all
10060 basic blocks or when there is a frame pointer and no stack realignment.
10061 But we first have to check that frame_pointer_rtx resp. arg_pointer_rtx
10062 has been eliminated. */
10063 if (!frame_pointer_needed)
10065 rtx reg, elim;
10067 if (!vt_stack_adjustments ())
10068 return false;
10070 #ifdef FRAME_POINTER_CFA_OFFSET
10071 reg = frame_pointer_rtx;
10072 #else
10073 reg = arg_pointer_rtx;
10074 #endif
10075 elim = eliminate_regs (reg, VOIDmode, NULL_RTX);
10076 if (elim != reg)
10078 if (GET_CODE (elim) == PLUS)
10079 elim = XEXP (elim, 0);
10080 if (elim == stack_pointer_rtx)
10081 vt_init_cfa_base ();
10084 else if (!crtl->stack_realign_tried)
10086 rtx reg, elim;
10088 #ifdef FRAME_POINTER_CFA_OFFSET
10089 reg = frame_pointer_rtx;
10090 fp_cfa_offset = FRAME_POINTER_CFA_OFFSET (current_function_decl);
10091 #else
10092 reg = arg_pointer_rtx;
10093 fp_cfa_offset = ARG_POINTER_CFA_OFFSET (current_function_decl);
10094 #endif
10095 elim = eliminate_regs (reg, VOIDmode, NULL_RTX);
10096 if (elim != reg)
10098 if (GET_CODE (elim) == PLUS)
10100 fp_cfa_offset -= rtx_to_poly_int64 (XEXP (elim, 1));
10101 elim = XEXP (elim, 0);
10103 if (elim != hard_frame_pointer_rtx)
10104 fp_cfa_offset = -1;
10106 else
10107 fp_cfa_offset = -1;
10110 /* If the stack is realigned and a DRAP register is used, we're going to
10111 rewrite MEMs based on it representing incoming locations of parameters
10112 passed on the stack into MEMs based on the argument pointer. Although
10113 we aren't going to rewrite other MEMs, we still need to initialize the
10114 virtual CFA pointer in order to ensure that the argument pointer will
10115 be seen as a constant throughout the function.
10117 ??? This doesn't work if FRAME_POINTER_CFA_OFFSET is defined. */
10118 else if (stack_realign_drap)
10120 rtx reg, elim;
10122 #ifdef FRAME_POINTER_CFA_OFFSET
10123 reg = frame_pointer_rtx;
10124 #else
10125 reg = arg_pointer_rtx;
10126 #endif
10127 elim = eliminate_regs (reg, VOIDmode, NULL_RTX);
10128 if (elim != reg)
10130 if (GET_CODE (elim) == PLUS)
10131 elim = XEXP (elim, 0);
10132 if (elim == hard_frame_pointer_rtx)
10133 vt_init_cfa_base ();
10137 hard_frame_pointer_adjustment = -1;
10139 vt_add_function_parameters ();
10141 FOR_EACH_BB_FN (bb, cfun)
10143 rtx_insn *insn;
10144 HOST_WIDE_INT pre, post = 0;
10145 basic_block first_bb, last_bb;
10147 if (MAY_HAVE_DEBUG_BIND_INSNS)
10149 cselib_record_sets_hook = add_with_sets;
10150 if (dump_file && (dump_flags & TDF_DETAILS))
10151 fprintf (dump_file, "first value: %i\n",
10152 cselib_get_next_uid ());
10155 first_bb = bb;
10156 for (;;)
10158 edge e;
10159 if (bb->next_bb == EXIT_BLOCK_PTR_FOR_FN (cfun)
10160 || ! single_pred_p (bb->next_bb))
10161 break;
10162 e = find_edge (bb, bb->next_bb);
10163 if (! e || (e->flags & EDGE_FALLTHRU) == 0)
10164 break;
10165 bb = bb->next_bb;
10167 last_bb = bb;
10169 /* Add the micro-operations to the vector. */
10170 FOR_BB_BETWEEN (bb, first_bb, last_bb->next_bb, next_bb)
10172 HOST_WIDE_INT offset = VTI (bb)->out.stack_adjust;
10173 VTI (bb)->out.stack_adjust = VTI (bb)->in.stack_adjust;
10175 rtx_insn *next;
10176 FOR_BB_INSNS_SAFE (bb, insn, next)
10178 if (INSN_P (insn))
10180 if (!frame_pointer_needed)
10182 insn_stack_adjust_offset_pre_post (insn, &pre, &post);
10183 if (pre)
10185 micro_operation mo;
10186 mo.type = MO_ADJUST;
10187 mo.u.adjust = pre;
10188 mo.insn = insn;
10189 if (dump_file && (dump_flags & TDF_DETAILS))
10190 log_op_type (PATTERN (insn), bb, insn,
10191 MO_ADJUST, dump_file);
10192 VTI (bb)->mos.safe_push (mo);
10193 VTI (bb)->out.stack_adjust += pre;
10197 cselib_hook_called = false;
10198 adjust_insn (bb, insn);
10199 if (DEBUG_MARKER_INSN_P (insn))
10201 reemit_marker_as_note (insn);
10202 continue;
10205 if (MAY_HAVE_DEBUG_BIND_INSNS)
10207 if (CALL_P (insn))
10208 prepare_call_arguments (bb, insn);
10209 cselib_process_insn (insn);
10210 if (dump_file && (dump_flags & TDF_DETAILS))
10212 print_rtl_single (dump_file, insn);
10213 dump_cselib_table (dump_file);
10216 if (!cselib_hook_called)
10217 add_with_sets (insn, 0, 0);
10218 cancel_changes (0);
10220 if (!frame_pointer_needed && post)
10222 micro_operation mo;
10223 mo.type = MO_ADJUST;
10224 mo.u.adjust = post;
10225 mo.insn = insn;
10226 if (dump_file && (dump_flags & TDF_DETAILS))
10227 log_op_type (PATTERN (insn), bb, insn,
10228 MO_ADJUST, dump_file);
10229 VTI (bb)->mos.safe_push (mo);
10230 VTI (bb)->out.stack_adjust += post;
10233 if (maybe_ne (fp_cfa_offset, -1)
10234 && known_eq (hard_frame_pointer_adjustment, -1)
10235 && fp_setter_insn (insn))
10237 vt_init_cfa_base ();
10238 hard_frame_pointer_adjustment = fp_cfa_offset;
10239 /* Disassociate sp from fp now. */
10240 if (MAY_HAVE_DEBUG_BIND_INSNS)
10242 cselib_val *v;
10243 cselib_invalidate_rtx (stack_pointer_rtx);
10244 v = cselib_lookup (stack_pointer_rtx, Pmode, 1,
10245 VOIDmode);
10246 if (v && !cselib_preserved_value_p (v))
10248 cselib_set_value_sp_based (v);
10249 preserve_value (v);
10255 gcc_assert (offset == VTI (bb)->out.stack_adjust);
10258 bb = last_bb;
10260 if (MAY_HAVE_DEBUG_BIND_INSNS)
10262 cselib_preserve_only_values ();
10263 cselib_reset_table (cselib_get_next_uid ());
10264 cselib_record_sets_hook = NULL;
10268 hard_frame_pointer_adjustment = -1;
10269 VTI (ENTRY_BLOCK_PTR_FOR_FN (cfun))->flooded = true;
10270 cfa_base_rtx = NULL_RTX;
10271 return true;
10274 /* This is *not* reset after each function. It gives each
10275 NOTE_INSN_DELETED_DEBUG_LABEL in the entire compilation
10276 a unique label number. */
10278 static int debug_label_num = 1;
10280 /* Remove from the insn stream a single debug insn used for
10281 variable tracking at assignments. */
10283 static inline void
10284 delete_vta_debug_insn (rtx_insn *insn)
10286 if (DEBUG_MARKER_INSN_P (insn))
10288 reemit_marker_as_note (insn);
10289 return;
10292 tree decl = INSN_VAR_LOCATION_DECL (insn);
10293 if (TREE_CODE (decl) == LABEL_DECL
10294 && DECL_NAME (decl)
10295 && !DECL_RTL_SET_P (decl))
10297 PUT_CODE (insn, NOTE);
10298 NOTE_KIND (insn) = NOTE_INSN_DELETED_DEBUG_LABEL;
10299 NOTE_DELETED_LABEL_NAME (insn)
10300 = IDENTIFIER_POINTER (DECL_NAME (decl));
10301 SET_DECL_RTL (decl, insn);
10302 CODE_LABEL_NUMBER (insn) = debug_label_num++;
10304 else
10305 delete_insn (insn);
10308 /* Remove from the insn stream all debug insns used for variable
10309 tracking at assignments. USE_CFG should be false if the cfg is no
10310 longer usable. */
10312 void
10313 delete_vta_debug_insns (bool use_cfg)
10315 basic_block bb;
10316 rtx_insn *insn, *next;
10318 if (!MAY_HAVE_DEBUG_INSNS)
10319 return;
10321 if (use_cfg)
10322 FOR_EACH_BB_FN (bb, cfun)
10324 FOR_BB_INSNS_SAFE (bb, insn, next)
10325 if (DEBUG_INSN_P (insn))
10326 delete_vta_debug_insn (insn);
10328 else
10329 for (insn = get_insns (); insn; insn = next)
10331 next = NEXT_INSN (insn);
10332 if (DEBUG_INSN_P (insn))
10333 delete_vta_debug_insn (insn);
10337 /* Run a fast, BB-local only version of var tracking, to take care of
10338 information that we don't do global analysis on, such that not all
10339 information is lost. If SKIPPED holds, we're skipping the global
10340 pass entirely, so we should try to use information it would have
10341 handled as well.. */
10343 static void
10344 vt_debug_insns_local (bool skipped ATTRIBUTE_UNUSED)
10346 /* ??? Just skip it all for now. */
10347 delete_vta_debug_insns (true);
10350 /* Free the data structures needed for variable tracking. */
10352 static void
10353 vt_finalize (void)
10355 basic_block bb;
10357 FOR_EACH_BB_FN (bb, cfun)
10359 VTI (bb)->mos.release ();
10362 FOR_ALL_BB_FN (bb, cfun)
10364 dataflow_set_destroy (&VTI (bb)->in);
10365 dataflow_set_destroy (&VTI (bb)->out);
10366 if (VTI (bb)->permp)
10368 dataflow_set_destroy (VTI (bb)->permp);
10369 XDELETE (VTI (bb)->permp);
10372 free_aux_for_blocks ();
10373 delete empty_shared_hash->htab;
10374 empty_shared_hash->htab = NULL;
10375 delete changed_variables;
10376 changed_variables = NULL;
10377 attrs_pool.release ();
10378 var_pool.release ();
10379 location_chain_pool.release ();
10380 shared_hash_pool.release ();
10382 if (MAY_HAVE_DEBUG_BIND_INSNS)
10384 if (global_get_addr_cache)
10385 delete global_get_addr_cache;
10386 global_get_addr_cache = NULL;
10387 loc_exp_dep_pool.release ();
10388 valvar_pool.release ();
10389 preserved_values.release ();
10390 cselib_finish ();
10391 BITMAP_FREE (scratch_regs);
10392 scratch_regs = NULL;
10395 #ifdef HAVE_window_save
10396 vec_free (windowed_parm_regs);
10397 #endif
10399 if (vui_vec)
10400 XDELETEVEC (vui_vec);
10401 vui_vec = NULL;
10402 vui_allocated = 0;
10405 /* The entry point to variable tracking pass. */
10407 static inline unsigned int
10408 variable_tracking_main_1 (void)
10410 bool success;
10412 /* We won't be called as a separate pass if flag_var_tracking is not
10413 set, but final may call us to turn debug markers into notes. */
10414 if ((!flag_var_tracking && MAY_HAVE_DEBUG_INSNS)
10415 || flag_var_tracking_assignments < 0
10416 /* Var-tracking right now assumes the IR doesn't contain
10417 any pseudos at this point. */
10418 || targetm.no_register_allocation)
10420 delete_vta_debug_insns (true);
10421 return 0;
10424 if (!flag_var_tracking)
10425 return 0;
10427 if (n_basic_blocks_for_fn (cfun) > 500
10428 && n_edges_for_fn (cfun) / n_basic_blocks_for_fn (cfun) >= 20)
10430 vt_debug_insns_local (true);
10431 return 0;
10434 mark_dfs_back_edges ();
10435 if (!vt_initialize ())
10437 vt_finalize ();
10438 vt_debug_insns_local (true);
10439 return 0;
10442 success = vt_find_locations ();
10444 if (!success && flag_var_tracking_assignments > 0)
10446 vt_finalize ();
10448 delete_vta_debug_insns (true);
10450 /* This is later restored by our caller. */
10451 flag_var_tracking_assignments = 0;
10453 success = vt_initialize ();
10454 gcc_assert (success);
10456 success = vt_find_locations ();
10459 if (!success)
10461 vt_finalize ();
10462 vt_debug_insns_local (false);
10463 return 0;
10466 if (dump_file && (dump_flags & TDF_DETAILS))
10468 dump_dataflow_sets ();
10469 dump_reg_info (dump_file);
10470 dump_flow_info (dump_file, dump_flags);
10473 timevar_push (TV_VAR_TRACKING_EMIT);
10474 vt_emit_notes ();
10475 timevar_pop (TV_VAR_TRACKING_EMIT);
10477 vt_finalize ();
10478 vt_debug_insns_local (false);
10479 return 0;
10482 unsigned int
10483 variable_tracking_main (void)
10485 unsigned int ret;
10486 int save = flag_var_tracking_assignments;
10488 ret = variable_tracking_main_1 ();
10490 flag_var_tracking_assignments = save;
10492 return ret;
10495 namespace {
10497 const pass_data pass_data_variable_tracking =
10499 RTL_PASS, /* type */
10500 "vartrack", /* name */
10501 OPTGROUP_NONE, /* optinfo_flags */
10502 TV_VAR_TRACKING, /* tv_id */
10503 0, /* properties_required */
10504 0, /* properties_provided */
10505 0, /* properties_destroyed */
10506 0, /* todo_flags_start */
10507 0, /* todo_flags_finish */
10510 class pass_variable_tracking : public rtl_opt_pass
10512 public:
10513 pass_variable_tracking (gcc::context *ctxt)
10514 : rtl_opt_pass (pass_data_variable_tracking, ctxt)
10517 /* opt_pass methods: */
10518 virtual bool gate (function *)
10520 return (flag_var_tracking && !targetm.delay_vartrack);
10523 virtual unsigned int execute (function *)
10525 return variable_tracking_main ();
10528 }; // class pass_variable_tracking
10530 } // anon namespace
10532 rtl_opt_pass *
10533 make_pass_variable_tracking (gcc::context *ctxt)
10535 return new pass_variable_tracking (ctxt);