* tree-ssa.c (target_for_debug_bind, verify_phi_args,
[official-gcc.git] / gcc / var-tracking.c
blobe405f0d81b3b07fdf9683c6f533a96df331e3aab
1 /* Variable tracking routines for the GNU compiler.
2 Copyright (C) 2002-2016 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 "tm_p.h"
99 #include "insn-config.h"
100 #include "regs.h"
101 #include "emit-rtl.h"
102 #include "recog.h"
103 #include "diagnostic.h"
104 #include "varasm.h"
105 #include "stor-layout.h"
106 #include "cfgrtl.h"
107 #include "cfganal.h"
108 #include "reload.h"
109 #include "calls.h"
110 #include "tree-dfa.h"
111 #include "tree-ssa.h"
112 #include "cselib.h"
113 #include "params.h"
114 #include "tree-pretty-print.h"
115 #include "rtl-iter.h"
116 #include "fibonacci_heap.h"
118 typedef fibonacci_heap <long, basic_block_def> bb_heap_t;
119 typedef fibonacci_node <long, basic_block_def> bb_heap_node_t;
121 /* var-tracking.c assumes that tree code with the same value as VALUE rtx code
122 has no chance to appear in REG_EXPR/MEM_EXPRs and isn't a decl.
123 Currently the value is the same as IDENTIFIER_NODE, which has such
124 a property. If this compile time assertion ever fails, make sure that
125 the new tree code that equals (int) VALUE has the same property. */
126 extern char check_value_val[(int) VALUE == (int) IDENTIFIER_NODE ? 1 : -1];
128 /* Type of micro operation. */
129 enum micro_operation_type
131 MO_USE, /* Use location (REG or MEM). */
132 MO_USE_NO_VAR,/* Use location which is not associated with a variable
133 or the variable is not trackable. */
134 MO_VAL_USE, /* Use location which is associated with a value. */
135 MO_VAL_LOC, /* Use location which appears in a debug insn. */
136 MO_VAL_SET, /* Set location associated with a value. */
137 MO_SET, /* Set location. */
138 MO_COPY, /* Copy the same portion of a variable from one
139 location to another. */
140 MO_CLOBBER, /* Clobber location. */
141 MO_CALL, /* Call insn. */
142 MO_ADJUST /* Adjust stack pointer. */
146 static const char * const ATTRIBUTE_UNUSED
147 micro_operation_type_name[] = {
148 "MO_USE",
149 "MO_USE_NO_VAR",
150 "MO_VAL_USE",
151 "MO_VAL_LOC",
152 "MO_VAL_SET",
153 "MO_SET",
154 "MO_COPY",
155 "MO_CLOBBER",
156 "MO_CALL",
157 "MO_ADJUST"
160 /* Where shall the note be emitted? BEFORE or AFTER the instruction.
161 Notes emitted as AFTER_CALL are to take effect during the call,
162 rather than after the call. */
163 enum emit_note_where
165 EMIT_NOTE_BEFORE_INSN,
166 EMIT_NOTE_AFTER_INSN,
167 EMIT_NOTE_AFTER_CALL_INSN
170 /* Structure holding information about micro operation. */
171 struct micro_operation
173 /* Type of micro operation. */
174 enum micro_operation_type type;
176 /* The instruction which the micro operation is in, for MO_USE,
177 MO_USE_NO_VAR, MO_CALL and MO_ADJUST, or the subsequent
178 instruction or note in the original flow (before any var-tracking
179 notes are inserted, to simplify emission of notes), for MO_SET
180 and MO_CLOBBER. */
181 rtx_insn *insn;
183 union {
184 /* Location. For MO_SET and MO_COPY, this is the SET that
185 performs the assignment, if known, otherwise it is the target
186 of the assignment. For MO_VAL_USE and MO_VAL_SET, it is a
187 CONCAT of the VALUE and the LOC associated with it. For
188 MO_VAL_LOC, it is a CONCAT of the VALUE and the VAR_LOCATION
189 associated with it. */
190 rtx loc;
192 /* Stack adjustment. */
193 HOST_WIDE_INT adjust;
194 } u;
198 /* A declaration of a variable, or an RTL value being handled like a
199 declaration. */
200 typedef void *decl_or_value;
202 /* Return true if a decl_or_value DV is a DECL or NULL. */
203 static inline bool
204 dv_is_decl_p (decl_or_value dv)
206 return !dv || (int) TREE_CODE ((tree) dv) != (int) VALUE;
209 /* Return true if a decl_or_value is a VALUE rtl. */
210 static inline bool
211 dv_is_value_p (decl_or_value dv)
213 return dv && !dv_is_decl_p (dv);
216 /* Return the decl in the decl_or_value. */
217 static inline tree
218 dv_as_decl (decl_or_value dv)
220 gcc_checking_assert (dv_is_decl_p (dv));
221 return (tree) dv;
224 /* Return the value in the decl_or_value. */
225 static inline rtx
226 dv_as_value (decl_or_value dv)
228 gcc_checking_assert (dv_is_value_p (dv));
229 return (rtx)dv;
232 /* Return the opaque pointer in the decl_or_value. */
233 static inline void *
234 dv_as_opaque (decl_or_value dv)
236 return dv;
240 /* Description of location of a part of a variable. The content of a physical
241 register is described by a chain of these structures.
242 The chains are pretty short (usually 1 or 2 elements) and thus
243 chain is the best data structure. */
244 struct attrs
246 /* Pointer to next member of the list. */
247 attrs *next;
249 /* The rtx of register. */
250 rtx loc;
252 /* The declaration corresponding to LOC. */
253 decl_or_value dv;
255 /* Offset from start of DECL. */
256 HOST_WIDE_INT offset;
259 /* Structure for chaining the locations. */
260 struct location_chain
262 /* Next element in the chain. */
263 location_chain *next;
265 /* The location (REG, MEM or VALUE). */
266 rtx loc;
268 /* The "value" stored in this location. */
269 rtx set_src;
271 /* Initialized? */
272 enum var_init_status init;
275 /* A vector of loc_exp_dep holds the active dependencies of a one-part
276 DV on VALUEs, i.e., the VALUEs expanded so as to form the current
277 location of DV. Each entry is also part of VALUE' s linked-list of
278 backlinks back to DV. */
279 struct loc_exp_dep
281 /* The dependent DV. */
282 decl_or_value dv;
283 /* The dependency VALUE or DECL_DEBUG. */
284 rtx value;
285 /* The next entry in VALUE's backlinks list. */
286 struct loc_exp_dep *next;
287 /* A pointer to the pointer to this entry (head or prev's next) in
288 the doubly-linked list. */
289 struct loc_exp_dep **pprev;
293 /* This data structure holds information about the depth of a variable
294 expansion. */
295 struct expand_depth
297 /* This measures the complexity of the expanded expression. It
298 grows by one for each level of expansion that adds more than one
299 operand. */
300 int complexity;
301 /* This counts the number of ENTRY_VALUE expressions in an
302 expansion. We want to minimize their use. */
303 int entryvals;
306 /* This data structure is allocated for one-part variables at the time
307 of emitting notes. */
308 struct onepart_aux
310 /* Doubly-linked list of dependent DVs. These are DVs whose cur_loc
311 computation used the expansion of this variable, and that ought
312 to be notified should this variable change. If the DV's cur_loc
313 expanded to NULL, all components of the loc list are regarded as
314 active, so that any changes in them give us a chance to get a
315 location. Otherwise, only components of the loc that expanded to
316 non-NULL are regarded as active dependencies. */
317 loc_exp_dep *backlinks;
318 /* This holds the LOC that was expanded into cur_loc. We need only
319 mark a one-part variable as changed if the FROM loc is removed,
320 or if it has no known location and a loc is added, or if it gets
321 a change notification from any of its active dependencies. */
322 rtx from;
323 /* The depth of the cur_loc expression. */
324 expand_depth depth;
325 /* Dependencies actively used when expand FROM into cur_loc. */
326 vec<loc_exp_dep, va_heap, vl_embed> deps;
329 /* Structure describing one part of variable. */
330 struct variable_part
332 /* Chain of locations of the part. */
333 location_chain *loc_chain;
335 /* Location which was last emitted to location list. */
336 rtx cur_loc;
338 union variable_aux
340 /* The offset in the variable, if !var->onepart. */
341 HOST_WIDE_INT offset;
343 /* Pointer to auxiliary data, if var->onepart and emit_notes. */
344 struct onepart_aux *onepaux;
345 } aux;
348 /* Maximum number of location parts. */
349 #define MAX_VAR_PARTS 16
351 /* Enumeration type used to discriminate various types of one-part
352 variables. */
353 enum onepart_enum
355 /* Not a one-part variable. */
356 NOT_ONEPART = 0,
357 /* A one-part DECL that is not a DEBUG_EXPR_DECL. */
358 ONEPART_VDECL = 1,
359 /* A DEBUG_EXPR_DECL. */
360 ONEPART_DEXPR = 2,
361 /* A VALUE. */
362 ONEPART_VALUE = 3
365 /* Structure describing where the variable is located. */
366 struct variable
368 /* The declaration of the variable, or an RTL value being handled
369 like a declaration. */
370 decl_or_value dv;
372 /* Reference count. */
373 int refcount;
375 /* Number of variable parts. */
376 char n_var_parts;
378 /* What type of DV this is, according to enum onepart_enum. */
379 ENUM_BITFIELD (onepart_enum) onepart : CHAR_BIT;
381 /* True if this variable_def struct is currently in the
382 changed_variables hash table. */
383 bool in_changed_variables;
385 /* The variable parts. */
386 variable_part var_part[1];
389 /* Pointer to the BB's information specific to variable tracking pass. */
390 #define VTI(BB) ((variable_tracking_info *) (BB)->aux)
392 /* Macro to access MEM_OFFSET as an HOST_WIDE_INT. Evaluates MEM twice. */
393 #define INT_MEM_OFFSET(mem) (MEM_OFFSET_KNOWN_P (mem) ? MEM_OFFSET (mem) : 0)
395 #if CHECKING_P && (GCC_VERSION >= 2007)
397 /* Access VAR's Ith part's offset, checking that it's not a one-part
398 variable. */
399 #define VAR_PART_OFFSET(var, i) __extension__ \
400 (*({ variable *const __v = (var); \
401 gcc_checking_assert (!__v->onepart); \
402 &__v->var_part[(i)].aux.offset; }))
404 /* Access VAR's one-part auxiliary data, checking that it is a
405 one-part variable. */
406 #define VAR_LOC_1PAUX(var) __extension__ \
407 (*({ variable *const __v = (var); \
408 gcc_checking_assert (__v->onepart); \
409 &__v->var_part[0].aux.onepaux; }))
411 #else
412 #define VAR_PART_OFFSET(var, i) ((var)->var_part[(i)].aux.offset)
413 #define VAR_LOC_1PAUX(var) ((var)->var_part[0].aux.onepaux)
414 #endif
416 /* These are accessor macros for the one-part auxiliary data. When
417 convenient for users, they're guarded by tests that the data was
418 allocated. */
419 #define VAR_LOC_DEP_LST(var) (VAR_LOC_1PAUX (var) \
420 ? VAR_LOC_1PAUX (var)->backlinks \
421 : NULL)
422 #define VAR_LOC_DEP_LSTP(var) (VAR_LOC_1PAUX (var) \
423 ? &VAR_LOC_1PAUX (var)->backlinks \
424 : NULL)
425 #define VAR_LOC_FROM(var) (VAR_LOC_1PAUX (var)->from)
426 #define VAR_LOC_DEPTH(var) (VAR_LOC_1PAUX (var)->depth)
427 #define VAR_LOC_DEP_VEC(var) (VAR_LOC_1PAUX (var) \
428 ? &VAR_LOC_1PAUX (var)->deps \
429 : NULL)
433 typedef unsigned int dvuid;
435 /* Return the uid of DV. */
437 static inline dvuid
438 dv_uid (decl_or_value dv)
440 if (dv_is_value_p (dv))
441 return CSELIB_VAL_PTR (dv_as_value (dv))->uid;
442 else
443 return DECL_UID (dv_as_decl (dv));
446 /* Compute the hash from the uid. */
448 static inline hashval_t
449 dv_uid2hash (dvuid uid)
451 return uid;
454 /* The hash function for a mask table in a shared_htab chain. */
456 static inline hashval_t
457 dv_htab_hash (decl_or_value dv)
459 return dv_uid2hash (dv_uid (dv));
462 static void variable_htab_free (void *);
464 /* Variable hashtable helpers. */
466 struct variable_hasher : pointer_hash <variable>
468 typedef void *compare_type;
469 static inline hashval_t hash (const variable *);
470 static inline bool equal (const variable *, const void *);
471 static inline void remove (variable *);
474 /* The hash function for variable_htab, computes the hash value
475 from the declaration of variable X. */
477 inline hashval_t
478 variable_hasher::hash (const variable *v)
480 return dv_htab_hash (v->dv);
483 /* Compare the declaration of variable X with declaration Y. */
485 inline bool
486 variable_hasher::equal (const variable *v, const void *y)
488 decl_or_value dv = CONST_CAST2 (decl_or_value, const void *, y);
490 return (dv_as_opaque (v->dv) == dv_as_opaque (dv));
493 /* Free the element of VARIABLE_HTAB (its type is struct variable_def). */
495 inline void
496 variable_hasher::remove (variable *var)
498 variable_htab_free (var);
501 typedef hash_table<variable_hasher> variable_table_type;
502 typedef variable_table_type::iterator variable_iterator_type;
504 /* Structure for passing some other parameters to function
505 emit_note_insn_var_location. */
506 struct emit_note_data
508 /* The instruction which the note will be emitted before/after. */
509 rtx_insn *insn;
511 /* Where the note will be emitted (before/after insn)? */
512 enum emit_note_where where;
514 /* The variables and values active at this point. */
515 variable_table_type *vars;
518 /* Structure holding a refcounted hash table. If refcount > 1,
519 it must be first unshared before modified. */
520 struct shared_hash
522 /* Reference count. */
523 int refcount;
525 /* Actual hash table. */
526 variable_table_type *htab;
529 /* Structure holding the IN or OUT set for a basic block. */
530 struct dataflow_set
532 /* Adjustment of stack offset. */
533 HOST_WIDE_INT stack_adjust;
535 /* Attributes for registers (lists of attrs). */
536 attrs *regs[FIRST_PSEUDO_REGISTER];
538 /* Variable locations. */
539 shared_hash *vars;
541 /* Vars that is being traversed. */
542 shared_hash *traversed_vars;
545 /* The structure (one for each basic block) containing the information
546 needed for variable tracking. */
547 struct variable_tracking_info
549 /* The vector of micro operations. */
550 vec<micro_operation> mos;
552 /* The IN and OUT set for dataflow analysis. */
553 dataflow_set in;
554 dataflow_set out;
556 /* The permanent-in dataflow set for this block. This is used to
557 hold values for which we had to compute entry values. ??? This
558 should probably be dynamically allocated, to avoid using more
559 memory in non-debug builds. */
560 dataflow_set *permp;
562 /* Has the block been visited in DFS? */
563 bool visited;
565 /* Has the block been flooded in VTA? */
566 bool flooded;
570 /* Alloc pool for struct attrs_def. */
571 object_allocator<attrs> attrs_pool ("attrs pool");
573 /* Alloc pool for struct variable_def with MAX_VAR_PARTS entries. */
575 static pool_allocator var_pool
576 ("variable_def pool", sizeof (variable) +
577 (MAX_VAR_PARTS - 1) * sizeof (((variable *)NULL)->var_part[0]));
579 /* Alloc pool for struct variable_def with a single var_part entry. */
580 static pool_allocator valvar_pool
581 ("small variable_def pool", sizeof (variable));
583 /* Alloc pool for struct location_chain. */
584 static object_allocator<location_chain> location_chain_pool
585 ("location_chain pool");
587 /* Alloc pool for struct shared_hash. */
588 static object_allocator<shared_hash> shared_hash_pool ("shared_hash pool");
590 /* Alloc pool for struct loc_exp_dep_s for NOT_ONEPART variables. */
591 object_allocator<loc_exp_dep> loc_exp_dep_pool ("loc_exp_dep pool");
593 /* Changed variables, notes will be emitted for them. */
594 static variable_table_type *changed_variables;
596 /* Shall notes be emitted? */
597 static bool emit_notes;
599 /* Values whose dynamic location lists have gone empty, but whose
600 cselib location lists are still usable. Use this to hold the
601 current location, the backlinks, etc, during emit_notes. */
602 static variable_table_type *dropped_values;
604 /* Empty shared hashtable. */
605 static shared_hash *empty_shared_hash;
607 /* Scratch register bitmap used by cselib_expand_value_rtx. */
608 static bitmap scratch_regs = NULL;
610 #ifdef HAVE_window_save
611 struct GTY(()) parm_reg {
612 rtx outgoing;
613 rtx incoming;
617 /* Vector of windowed parameter registers, if any. */
618 static vec<parm_reg, va_gc> *windowed_parm_regs = NULL;
619 #endif
621 /* Variable used to tell whether cselib_process_insn called our hook. */
622 static bool cselib_hook_called;
624 /* Local function prototypes. */
625 static void stack_adjust_offset_pre_post (rtx, HOST_WIDE_INT *,
626 HOST_WIDE_INT *);
627 static void insn_stack_adjust_offset_pre_post (rtx_insn *, HOST_WIDE_INT *,
628 HOST_WIDE_INT *);
629 static bool vt_stack_adjustments (void);
631 static void init_attrs_list_set (attrs **);
632 static void attrs_list_clear (attrs **);
633 static attrs *attrs_list_member (attrs *, decl_or_value, HOST_WIDE_INT);
634 static void attrs_list_insert (attrs **, decl_or_value, HOST_WIDE_INT, rtx);
635 static void attrs_list_copy (attrs **, attrs *);
636 static void attrs_list_union (attrs **, attrs *);
638 static variable **unshare_variable (dataflow_set *set, variable **slot,
639 variable *var, enum var_init_status);
640 static void vars_copy (variable_table_type *, variable_table_type *);
641 static tree var_debug_decl (tree);
642 static void var_reg_set (dataflow_set *, rtx, enum var_init_status, rtx);
643 static void var_reg_delete_and_set (dataflow_set *, rtx, bool,
644 enum var_init_status, rtx);
645 static void var_reg_delete (dataflow_set *, rtx, bool);
646 static void var_regno_delete (dataflow_set *, int);
647 static void var_mem_set (dataflow_set *, rtx, enum var_init_status, rtx);
648 static void var_mem_delete_and_set (dataflow_set *, rtx, bool,
649 enum var_init_status, rtx);
650 static void var_mem_delete (dataflow_set *, rtx, bool);
652 static void dataflow_set_init (dataflow_set *);
653 static void dataflow_set_clear (dataflow_set *);
654 static void dataflow_set_copy (dataflow_set *, dataflow_set *);
655 static int variable_union_info_cmp_pos (const void *, const void *);
656 static void dataflow_set_union (dataflow_set *, dataflow_set *);
657 static location_chain *find_loc_in_1pdv (rtx, variable *,
658 variable_table_type *);
659 static bool canon_value_cmp (rtx, rtx);
660 static int loc_cmp (rtx, rtx);
661 static bool variable_part_different_p (variable_part *, variable_part *);
662 static bool onepart_variable_different_p (variable *, variable *);
663 static bool variable_different_p (variable *, variable *);
664 static bool dataflow_set_different (dataflow_set *, dataflow_set *);
665 static void dataflow_set_destroy (dataflow_set *);
667 static bool track_expr_p (tree, bool);
668 static bool same_variable_part_p (rtx, tree, HOST_WIDE_INT);
669 static void add_uses_1 (rtx *, void *);
670 static void add_stores (rtx, const_rtx, void *);
671 static bool compute_bb_dataflow (basic_block);
672 static bool vt_find_locations (void);
674 static void dump_attrs_list (attrs *);
675 static void dump_var (variable *);
676 static void dump_vars (variable_table_type *);
677 static void dump_dataflow_set (dataflow_set *);
678 static void dump_dataflow_sets (void);
680 static void set_dv_changed (decl_or_value, bool);
681 static void variable_was_changed (variable *, dataflow_set *);
682 static variable **set_slot_part (dataflow_set *, rtx, variable **,
683 decl_or_value, HOST_WIDE_INT,
684 enum var_init_status, rtx);
685 static void set_variable_part (dataflow_set *, rtx,
686 decl_or_value, HOST_WIDE_INT,
687 enum var_init_status, rtx, enum insert_option);
688 static variable **clobber_slot_part (dataflow_set *, rtx,
689 variable **, HOST_WIDE_INT, rtx);
690 static void clobber_variable_part (dataflow_set *, rtx,
691 decl_or_value, HOST_WIDE_INT, rtx);
692 static variable **delete_slot_part (dataflow_set *, rtx, variable **,
693 HOST_WIDE_INT);
694 static void delete_variable_part (dataflow_set *, rtx,
695 decl_or_value, HOST_WIDE_INT);
696 static void emit_notes_in_bb (basic_block, dataflow_set *);
697 static void vt_emit_notes (void);
699 static bool vt_get_decl_and_offset (rtx, tree *, HOST_WIDE_INT *);
700 static void vt_add_function_parameters (void);
701 static bool vt_initialize (void);
702 static void vt_finalize (void);
704 /* Callback for stack_adjust_offset_pre_post, called via for_each_inc_dec. */
706 static int
707 stack_adjust_offset_pre_post_cb (rtx, rtx op, rtx dest, rtx src, rtx srcoff,
708 void *arg)
710 if (dest != stack_pointer_rtx)
711 return 0;
713 switch (GET_CODE (op))
715 case PRE_INC:
716 case PRE_DEC:
717 ((HOST_WIDE_INT *)arg)[0] -= INTVAL (srcoff);
718 return 0;
719 case POST_INC:
720 case POST_DEC:
721 ((HOST_WIDE_INT *)arg)[1] -= INTVAL (srcoff);
722 return 0;
723 case PRE_MODIFY:
724 case POST_MODIFY:
725 /* We handle only adjustments by constant amount. */
726 gcc_assert (GET_CODE (src) == PLUS
727 && CONST_INT_P (XEXP (src, 1))
728 && XEXP (src, 0) == stack_pointer_rtx);
729 ((HOST_WIDE_INT *)arg)[GET_CODE (op) == POST_MODIFY]
730 -= INTVAL (XEXP (src, 1));
731 return 0;
732 default:
733 gcc_unreachable ();
737 /* Given a SET, calculate the amount of stack adjustment it contains
738 PRE- and POST-modifying stack pointer.
739 This function is similar to stack_adjust_offset. */
741 static void
742 stack_adjust_offset_pre_post (rtx pattern, HOST_WIDE_INT *pre,
743 HOST_WIDE_INT *post)
745 rtx src = SET_SRC (pattern);
746 rtx dest = SET_DEST (pattern);
747 enum rtx_code code;
749 if (dest == stack_pointer_rtx)
751 /* (set (reg sp) (plus (reg sp) (const_int))) */
752 code = GET_CODE (src);
753 if (! (code == PLUS || code == MINUS)
754 || XEXP (src, 0) != stack_pointer_rtx
755 || !CONST_INT_P (XEXP (src, 1)))
756 return;
758 if (code == MINUS)
759 *post += INTVAL (XEXP (src, 1));
760 else
761 *post -= INTVAL (XEXP (src, 1));
762 return;
764 HOST_WIDE_INT res[2] = { 0, 0 };
765 for_each_inc_dec (pattern, stack_adjust_offset_pre_post_cb, res);
766 *pre += res[0];
767 *post += res[1];
770 /* Given an INSN, calculate the amount of stack adjustment it contains
771 PRE- and POST-modifying stack pointer. */
773 static void
774 insn_stack_adjust_offset_pre_post (rtx_insn *insn, HOST_WIDE_INT *pre,
775 HOST_WIDE_INT *post)
777 rtx pattern;
779 *pre = 0;
780 *post = 0;
782 pattern = PATTERN (insn);
783 if (RTX_FRAME_RELATED_P (insn))
785 rtx expr = find_reg_note (insn, REG_FRAME_RELATED_EXPR, NULL_RTX);
786 if (expr)
787 pattern = XEXP (expr, 0);
790 if (GET_CODE (pattern) == SET)
791 stack_adjust_offset_pre_post (pattern, pre, post);
792 else if (GET_CODE (pattern) == PARALLEL
793 || GET_CODE (pattern) == SEQUENCE)
795 int i;
797 /* There may be stack adjustments inside compound insns. Search
798 for them. */
799 for ( i = XVECLEN (pattern, 0) - 1; i >= 0; i--)
800 if (GET_CODE (XVECEXP (pattern, 0, i)) == SET)
801 stack_adjust_offset_pre_post (XVECEXP (pattern, 0, i), pre, post);
805 /* Compute stack adjustments for all blocks by traversing DFS tree.
806 Return true when the adjustments on all incoming edges are consistent.
807 Heavily borrowed from pre_and_rev_post_order_compute. */
809 static bool
810 vt_stack_adjustments (void)
812 edge_iterator *stack;
813 int sp;
815 /* Initialize entry block. */
816 VTI (ENTRY_BLOCK_PTR_FOR_FN (cfun))->visited = true;
817 VTI (ENTRY_BLOCK_PTR_FOR_FN (cfun))->in.stack_adjust
818 = INCOMING_FRAME_SP_OFFSET;
819 VTI (ENTRY_BLOCK_PTR_FOR_FN (cfun))->out.stack_adjust
820 = INCOMING_FRAME_SP_OFFSET;
822 /* Allocate stack for back-tracking up CFG. */
823 stack = XNEWVEC (edge_iterator, n_basic_blocks_for_fn (cfun) + 1);
824 sp = 0;
826 /* Push the first edge on to the stack. */
827 stack[sp++] = ei_start (ENTRY_BLOCK_PTR_FOR_FN (cfun)->succs);
829 while (sp)
831 edge_iterator ei;
832 basic_block src;
833 basic_block dest;
835 /* Look at the edge on the top of the stack. */
836 ei = stack[sp - 1];
837 src = ei_edge (ei)->src;
838 dest = ei_edge (ei)->dest;
840 /* Check if the edge destination has been visited yet. */
841 if (!VTI (dest)->visited)
843 rtx_insn *insn;
844 HOST_WIDE_INT pre, post, offset;
845 VTI (dest)->visited = true;
846 VTI (dest)->in.stack_adjust = offset = VTI (src)->out.stack_adjust;
848 if (dest != EXIT_BLOCK_PTR_FOR_FN (cfun))
849 for (insn = BB_HEAD (dest);
850 insn != NEXT_INSN (BB_END (dest));
851 insn = NEXT_INSN (insn))
852 if (INSN_P (insn))
854 insn_stack_adjust_offset_pre_post (insn, &pre, &post);
855 offset += pre + post;
858 VTI (dest)->out.stack_adjust = offset;
860 if (EDGE_COUNT (dest->succs) > 0)
861 /* Since the DEST node has been visited for the first
862 time, check its successors. */
863 stack[sp++] = ei_start (dest->succs);
865 else
867 /* We can end up with different stack adjustments for the exit block
868 of a shrink-wrapped function if stack_adjust_offset_pre_post
869 doesn't understand the rtx pattern used to restore the stack
870 pointer in the epilogue. For example, on s390(x), the stack
871 pointer is often restored via a load-multiple instruction
872 and so no stack_adjust offset is recorded for it. This means
873 that the stack offset at the end of the epilogue block is the
874 same as the offset before the epilogue, whereas other paths
875 to the exit block will have the correct stack_adjust.
877 It is safe to ignore these differences because (a) we never
878 use the stack_adjust for the exit block in this pass and
879 (b) dwarf2cfi checks whether the CFA notes in a shrink-wrapped
880 function are correct.
882 We must check whether the adjustments on other edges are
883 the same though. */
884 if (dest != EXIT_BLOCK_PTR_FOR_FN (cfun)
885 && VTI (dest)->in.stack_adjust != VTI (src)->out.stack_adjust)
887 free (stack);
888 return false;
891 if (! ei_one_before_end_p (ei))
892 /* Go to the next edge. */
893 ei_next (&stack[sp - 1]);
894 else
895 /* Return to previous level if there are no more edges. */
896 sp--;
900 free (stack);
901 return true;
904 /* arg_pointer_rtx resp. frame_pointer_rtx if stack_pointer_rtx or
905 hard_frame_pointer_rtx is being mapped to it and offset for it. */
906 static rtx cfa_base_rtx;
907 static HOST_WIDE_INT cfa_base_offset;
909 /* Compute a CFA-based value for an ADJUSTMENT made to stack_pointer_rtx
910 or hard_frame_pointer_rtx. */
912 static inline rtx
913 compute_cfa_pointer (HOST_WIDE_INT adjustment)
915 return plus_constant (Pmode, cfa_base_rtx, adjustment + cfa_base_offset);
918 /* Adjustment for hard_frame_pointer_rtx to cfa base reg,
919 or -1 if the replacement shouldn't be done. */
920 static HOST_WIDE_INT hard_frame_pointer_adjustment = -1;
922 /* Data for adjust_mems callback. */
924 struct adjust_mem_data
926 bool store;
927 machine_mode mem_mode;
928 HOST_WIDE_INT stack_adjust;
929 auto_vec<rtx> side_effects;
932 /* Helper for adjust_mems. Return true if X is suitable for
933 transformation of wider mode arithmetics to narrower mode. */
935 static bool
936 use_narrower_mode_test (rtx x, const_rtx subreg)
938 subrtx_var_iterator::array_type array;
939 FOR_EACH_SUBRTX_VAR (iter, array, x, NONCONST)
941 rtx x = *iter;
942 if (CONSTANT_P (x))
943 iter.skip_subrtxes ();
944 else
945 switch (GET_CODE (x))
947 case REG:
948 if (cselib_lookup (x, GET_MODE (SUBREG_REG (subreg)), 0, VOIDmode))
949 return false;
950 if (!validate_subreg (GET_MODE (subreg), GET_MODE (x), x,
951 subreg_lowpart_offset (GET_MODE (subreg),
952 GET_MODE (x))))
953 return false;
954 break;
955 case PLUS:
956 case MINUS:
957 case MULT:
958 break;
959 case ASHIFT:
960 iter.substitute (XEXP (x, 0));
961 break;
962 default:
963 return false;
966 return true;
969 /* Transform X into narrower mode MODE from wider mode WMODE. */
971 static rtx
972 use_narrower_mode (rtx x, machine_mode mode, machine_mode wmode)
974 rtx op0, op1;
975 if (CONSTANT_P (x))
976 return lowpart_subreg (mode, x, wmode);
977 switch (GET_CODE (x))
979 case REG:
980 return lowpart_subreg (mode, x, wmode);
981 case PLUS:
982 case MINUS:
983 case MULT:
984 op0 = use_narrower_mode (XEXP (x, 0), mode, wmode);
985 op1 = use_narrower_mode (XEXP (x, 1), mode, wmode);
986 return simplify_gen_binary (GET_CODE (x), mode, op0, op1);
987 case ASHIFT:
988 op0 = use_narrower_mode (XEXP (x, 0), mode, wmode);
989 op1 = XEXP (x, 1);
990 /* Ensure shift amount is not wider than mode. */
991 if (GET_MODE (op1) == VOIDmode)
992 op1 = lowpart_subreg (mode, op1, wmode);
993 else if (GET_MODE_PRECISION (mode) < GET_MODE_PRECISION (GET_MODE (op1)))
994 op1 = lowpart_subreg (mode, op1, GET_MODE (op1));
995 return simplify_gen_binary (ASHIFT, mode, op0, op1);
996 default:
997 gcc_unreachable ();
1001 /* Helper function for adjusting used MEMs. */
1003 static rtx
1004 adjust_mems (rtx loc, const_rtx old_rtx, void *data)
1006 struct adjust_mem_data *amd = (struct adjust_mem_data *) data;
1007 rtx mem, addr = loc, tem;
1008 machine_mode mem_mode_save;
1009 bool store_save;
1010 switch (GET_CODE (loc))
1012 case REG:
1013 /* Don't do any sp or fp replacements outside of MEM addresses
1014 on the LHS. */
1015 if (amd->mem_mode == VOIDmode && amd->store)
1016 return loc;
1017 if (loc == stack_pointer_rtx
1018 && !frame_pointer_needed
1019 && cfa_base_rtx)
1020 return compute_cfa_pointer (amd->stack_adjust);
1021 else if (loc == hard_frame_pointer_rtx
1022 && frame_pointer_needed
1023 && hard_frame_pointer_adjustment != -1
1024 && cfa_base_rtx)
1025 return compute_cfa_pointer (hard_frame_pointer_adjustment);
1026 gcc_checking_assert (loc != virtual_incoming_args_rtx);
1027 return loc;
1028 case MEM:
1029 mem = loc;
1030 if (!amd->store)
1032 mem = targetm.delegitimize_address (mem);
1033 if (mem != loc && !MEM_P (mem))
1034 return simplify_replace_fn_rtx (mem, old_rtx, adjust_mems, data);
1037 addr = XEXP (mem, 0);
1038 mem_mode_save = amd->mem_mode;
1039 amd->mem_mode = GET_MODE (mem);
1040 store_save = amd->store;
1041 amd->store = false;
1042 addr = simplify_replace_fn_rtx (addr, old_rtx, adjust_mems, data);
1043 amd->store = store_save;
1044 amd->mem_mode = mem_mode_save;
1045 if (mem == loc)
1046 addr = targetm.delegitimize_address (addr);
1047 if (addr != XEXP (mem, 0))
1048 mem = replace_equiv_address_nv (mem, addr);
1049 if (!amd->store)
1050 mem = avoid_constant_pool_reference (mem);
1051 return mem;
1052 case PRE_INC:
1053 case PRE_DEC:
1054 addr = gen_rtx_PLUS (GET_MODE (loc), XEXP (loc, 0),
1055 gen_int_mode (GET_CODE (loc) == PRE_INC
1056 ? GET_MODE_SIZE (amd->mem_mode)
1057 : -GET_MODE_SIZE (amd->mem_mode),
1058 GET_MODE (loc)));
1059 /* FALLTHRU */
1060 case POST_INC:
1061 case POST_DEC:
1062 if (addr == loc)
1063 addr = XEXP (loc, 0);
1064 gcc_assert (amd->mem_mode != VOIDmode && amd->mem_mode != BLKmode);
1065 addr = simplify_replace_fn_rtx (addr, old_rtx, adjust_mems, data);
1066 tem = gen_rtx_PLUS (GET_MODE (loc), XEXP (loc, 0),
1067 gen_int_mode ((GET_CODE (loc) == PRE_INC
1068 || GET_CODE (loc) == POST_INC)
1069 ? GET_MODE_SIZE (amd->mem_mode)
1070 : -GET_MODE_SIZE (amd->mem_mode),
1071 GET_MODE (loc)));
1072 store_save = amd->store;
1073 amd->store = false;
1074 tem = simplify_replace_fn_rtx (tem, old_rtx, adjust_mems, data);
1075 amd->store = store_save;
1076 amd->side_effects.safe_push (gen_rtx_SET (XEXP (loc, 0), tem));
1077 return addr;
1078 case PRE_MODIFY:
1079 addr = XEXP (loc, 1);
1080 /* FALLTHRU */
1081 case POST_MODIFY:
1082 if (addr == loc)
1083 addr = XEXP (loc, 0);
1084 gcc_assert (amd->mem_mode != VOIDmode);
1085 addr = simplify_replace_fn_rtx (addr, old_rtx, adjust_mems, data);
1086 store_save = amd->store;
1087 amd->store = false;
1088 tem = simplify_replace_fn_rtx (XEXP (loc, 1), old_rtx,
1089 adjust_mems, data);
1090 amd->store = store_save;
1091 amd->side_effects.safe_push (gen_rtx_SET (XEXP (loc, 0), tem));
1092 return addr;
1093 case SUBREG:
1094 /* First try without delegitimization of whole MEMs and
1095 avoid_constant_pool_reference, which is more likely to succeed. */
1096 store_save = amd->store;
1097 amd->store = true;
1098 addr = simplify_replace_fn_rtx (SUBREG_REG (loc), old_rtx, adjust_mems,
1099 data);
1100 amd->store = store_save;
1101 mem = simplify_replace_fn_rtx (addr, old_rtx, adjust_mems, data);
1102 if (mem == SUBREG_REG (loc))
1104 tem = loc;
1105 goto finish_subreg;
1107 tem = simplify_gen_subreg (GET_MODE (loc), mem,
1108 GET_MODE (SUBREG_REG (loc)),
1109 SUBREG_BYTE (loc));
1110 if (tem)
1111 goto finish_subreg;
1112 tem = simplify_gen_subreg (GET_MODE (loc), addr,
1113 GET_MODE (SUBREG_REG (loc)),
1114 SUBREG_BYTE (loc));
1115 if (tem == NULL_RTX)
1116 tem = gen_rtx_raw_SUBREG (GET_MODE (loc), addr, SUBREG_BYTE (loc));
1117 finish_subreg:
1118 if (MAY_HAVE_DEBUG_INSNS
1119 && GET_CODE (tem) == SUBREG
1120 && (GET_CODE (SUBREG_REG (tem)) == PLUS
1121 || GET_CODE (SUBREG_REG (tem)) == MINUS
1122 || GET_CODE (SUBREG_REG (tem)) == MULT
1123 || GET_CODE (SUBREG_REG (tem)) == ASHIFT)
1124 && (GET_MODE_CLASS (GET_MODE (tem)) == MODE_INT
1125 || GET_MODE_CLASS (GET_MODE (tem)) == MODE_PARTIAL_INT)
1126 && (GET_MODE_CLASS (GET_MODE (SUBREG_REG (tem))) == MODE_INT
1127 || GET_MODE_CLASS (GET_MODE (SUBREG_REG (tem))) == MODE_PARTIAL_INT)
1128 && GET_MODE_PRECISION (GET_MODE (tem))
1129 < GET_MODE_PRECISION (GET_MODE (SUBREG_REG (tem)))
1130 && subreg_lowpart_p (tem)
1131 && use_narrower_mode_test (SUBREG_REG (tem), tem))
1132 return use_narrower_mode (SUBREG_REG (tem), GET_MODE (tem),
1133 GET_MODE (SUBREG_REG (tem)));
1134 return tem;
1135 case ASM_OPERANDS:
1136 /* Don't do any replacements in second and following
1137 ASM_OPERANDS of inline-asm with multiple sets.
1138 ASM_OPERANDS_INPUT_VEC, ASM_OPERANDS_INPUT_CONSTRAINT_VEC
1139 and ASM_OPERANDS_LABEL_VEC need to be equal between
1140 all the ASM_OPERANDs in the insn and adjust_insn will
1141 fix this up. */
1142 if (ASM_OPERANDS_OUTPUT_IDX (loc) != 0)
1143 return loc;
1144 break;
1145 default:
1146 break;
1148 return NULL_RTX;
1151 /* Helper function for replacement of uses. */
1153 static void
1154 adjust_mem_uses (rtx *x, void *data)
1156 rtx new_x = simplify_replace_fn_rtx (*x, NULL_RTX, adjust_mems, data);
1157 if (new_x != *x)
1158 validate_change (NULL_RTX, x, new_x, true);
1161 /* Helper function for replacement of stores. */
1163 static void
1164 adjust_mem_stores (rtx loc, const_rtx expr, void *data)
1166 if (MEM_P (loc))
1168 rtx new_dest = simplify_replace_fn_rtx (SET_DEST (expr), NULL_RTX,
1169 adjust_mems, data);
1170 if (new_dest != SET_DEST (expr))
1172 rtx xexpr = CONST_CAST_RTX (expr);
1173 validate_change (NULL_RTX, &SET_DEST (xexpr), new_dest, true);
1178 /* Simplify INSN. Remove all {PRE,POST}_{INC,DEC,MODIFY} rtxes,
1179 replace them with their value in the insn and add the side-effects
1180 as other sets to the insn. */
1182 static void
1183 adjust_insn (basic_block bb, rtx_insn *insn)
1185 rtx set;
1187 #ifdef HAVE_window_save
1188 /* If the target machine has an explicit window save instruction, the
1189 transformation OUTGOING_REGNO -> INCOMING_REGNO is done there. */
1190 if (RTX_FRAME_RELATED_P (insn)
1191 && find_reg_note (insn, REG_CFA_WINDOW_SAVE, NULL_RTX))
1193 unsigned int i, nregs = vec_safe_length (windowed_parm_regs);
1194 rtx rtl = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (nregs * 2));
1195 parm_reg *p;
1197 FOR_EACH_VEC_SAFE_ELT (windowed_parm_regs, i, p)
1199 XVECEXP (rtl, 0, i * 2)
1200 = gen_rtx_SET (p->incoming, p->outgoing);
1201 /* Do not clobber the attached DECL, but only the REG. */
1202 XVECEXP (rtl, 0, i * 2 + 1)
1203 = gen_rtx_CLOBBER (GET_MODE (p->outgoing),
1204 gen_raw_REG (GET_MODE (p->outgoing),
1205 REGNO (p->outgoing)));
1208 validate_change (NULL_RTX, &PATTERN (insn), rtl, true);
1209 return;
1211 #endif
1213 adjust_mem_data amd;
1214 amd.mem_mode = VOIDmode;
1215 amd.stack_adjust = -VTI (bb)->out.stack_adjust;
1217 amd.store = true;
1218 note_stores (PATTERN (insn), adjust_mem_stores, &amd);
1220 amd.store = false;
1221 if (GET_CODE (PATTERN (insn)) == PARALLEL
1222 && asm_noperands (PATTERN (insn)) > 0
1223 && GET_CODE (XVECEXP (PATTERN (insn), 0, 0)) == SET)
1225 rtx body, set0;
1226 int i;
1228 /* inline-asm with multiple sets is tiny bit more complicated,
1229 because the 3 vectors in ASM_OPERANDS need to be shared between
1230 all ASM_OPERANDS in the instruction. adjust_mems will
1231 not touch ASM_OPERANDS other than the first one, asm_noperands
1232 test above needs to be called before that (otherwise it would fail)
1233 and afterwards this code fixes it up. */
1234 note_uses (&PATTERN (insn), adjust_mem_uses, &amd);
1235 body = PATTERN (insn);
1236 set0 = XVECEXP (body, 0, 0);
1237 gcc_checking_assert (GET_CODE (set0) == SET
1238 && GET_CODE (SET_SRC (set0)) == ASM_OPERANDS
1239 && ASM_OPERANDS_OUTPUT_IDX (SET_SRC (set0)) == 0);
1240 for (i = 1; i < XVECLEN (body, 0); i++)
1241 if (GET_CODE (XVECEXP (body, 0, i)) != SET)
1242 break;
1243 else
1245 set = XVECEXP (body, 0, i);
1246 gcc_checking_assert (GET_CODE (SET_SRC (set)) == ASM_OPERANDS
1247 && ASM_OPERANDS_OUTPUT_IDX (SET_SRC (set))
1248 == i);
1249 if (ASM_OPERANDS_INPUT_VEC (SET_SRC (set))
1250 != ASM_OPERANDS_INPUT_VEC (SET_SRC (set0))
1251 || ASM_OPERANDS_INPUT_CONSTRAINT_VEC (SET_SRC (set))
1252 != ASM_OPERANDS_INPUT_CONSTRAINT_VEC (SET_SRC (set0))
1253 || ASM_OPERANDS_LABEL_VEC (SET_SRC (set))
1254 != ASM_OPERANDS_LABEL_VEC (SET_SRC (set0)))
1256 rtx newsrc = shallow_copy_rtx (SET_SRC (set));
1257 ASM_OPERANDS_INPUT_VEC (newsrc)
1258 = ASM_OPERANDS_INPUT_VEC (SET_SRC (set0));
1259 ASM_OPERANDS_INPUT_CONSTRAINT_VEC (newsrc)
1260 = ASM_OPERANDS_INPUT_CONSTRAINT_VEC (SET_SRC (set0));
1261 ASM_OPERANDS_LABEL_VEC (newsrc)
1262 = ASM_OPERANDS_LABEL_VEC (SET_SRC (set0));
1263 validate_change (NULL_RTX, &SET_SRC (set), newsrc, true);
1267 else
1268 note_uses (&PATTERN (insn), adjust_mem_uses, &amd);
1270 /* For read-only MEMs containing some constant, prefer those
1271 constants. */
1272 set = single_set (insn);
1273 if (set && MEM_P (SET_SRC (set)) && MEM_READONLY_P (SET_SRC (set)))
1275 rtx note = find_reg_equal_equiv_note (insn);
1277 if (note && CONSTANT_P (XEXP (note, 0)))
1278 validate_change (NULL_RTX, &SET_SRC (set), XEXP (note, 0), true);
1281 if (!amd.side_effects.is_empty ())
1283 rtx *pat, new_pat;
1284 int i, oldn;
1286 pat = &PATTERN (insn);
1287 if (GET_CODE (*pat) == COND_EXEC)
1288 pat = &COND_EXEC_CODE (*pat);
1289 if (GET_CODE (*pat) == PARALLEL)
1290 oldn = XVECLEN (*pat, 0);
1291 else
1292 oldn = 1;
1293 unsigned int newn = amd.side_effects.length ();
1294 new_pat = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (oldn + newn));
1295 if (GET_CODE (*pat) == PARALLEL)
1296 for (i = 0; i < oldn; i++)
1297 XVECEXP (new_pat, 0, i) = XVECEXP (*pat, 0, i);
1298 else
1299 XVECEXP (new_pat, 0, 0) = *pat;
1301 rtx effect;
1302 unsigned int j;
1303 FOR_EACH_VEC_ELT_REVERSE (amd.side_effects, j, effect)
1304 XVECEXP (new_pat, 0, j + oldn) = effect;
1305 validate_change (NULL_RTX, pat, new_pat, true);
1309 /* Return the DEBUG_EXPR of a DEBUG_EXPR_DECL or the VALUE in DV. */
1310 static inline rtx
1311 dv_as_rtx (decl_or_value dv)
1313 tree decl;
1315 if (dv_is_value_p (dv))
1316 return dv_as_value (dv);
1318 decl = dv_as_decl (dv);
1320 gcc_checking_assert (TREE_CODE (decl) == DEBUG_EXPR_DECL);
1321 return DECL_RTL_KNOWN_SET (decl);
1324 /* Return nonzero if a decl_or_value must not have more than one
1325 variable part. The returned value discriminates among various
1326 kinds of one-part DVs ccording to enum onepart_enum. */
1327 static inline onepart_enum
1328 dv_onepart_p (decl_or_value dv)
1330 tree decl;
1332 if (!MAY_HAVE_DEBUG_INSNS)
1333 return NOT_ONEPART;
1335 if (dv_is_value_p (dv))
1336 return ONEPART_VALUE;
1338 decl = dv_as_decl (dv);
1340 if (TREE_CODE (decl) == DEBUG_EXPR_DECL)
1341 return ONEPART_DEXPR;
1343 if (target_for_debug_bind (decl) != NULL_TREE)
1344 return ONEPART_VDECL;
1346 return NOT_ONEPART;
1349 /* Return the variable pool to be used for a dv of type ONEPART. */
1350 static inline pool_allocator &
1351 onepart_pool (onepart_enum onepart)
1353 return onepart ? valvar_pool : var_pool;
1356 /* Allocate a variable_def from the corresponding variable pool. */
1357 static inline variable *
1358 onepart_pool_allocate (onepart_enum onepart)
1360 return (variable*) onepart_pool (onepart).allocate ();
1363 /* Build a decl_or_value out of a decl. */
1364 static inline decl_or_value
1365 dv_from_decl (tree decl)
1367 decl_or_value dv;
1368 dv = decl;
1369 gcc_checking_assert (dv_is_decl_p (dv));
1370 return dv;
1373 /* Build a decl_or_value out of a value. */
1374 static inline decl_or_value
1375 dv_from_value (rtx value)
1377 decl_or_value dv;
1378 dv = value;
1379 gcc_checking_assert (dv_is_value_p (dv));
1380 return dv;
1383 /* Return a value or the decl of a debug_expr as a decl_or_value. */
1384 static inline decl_or_value
1385 dv_from_rtx (rtx x)
1387 decl_or_value dv;
1389 switch (GET_CODE (x))
1391 case DEBUG_EXPR:
1392 dv = dv_from_decl (DEBUG_EXPR_TREE_DECL (x));
1393 gcc_checking_assert (DECL_RTL_KNOWN_SET (DEBUG_EXPR_TREE_DECL (x)) == x);
1394 break;
1396 case VALUE:
1397 dv = dv_from_value (x);
1398 break;
1400 default:
1401 gcc_unreachable ();
1404 return dv;
1407 extern void debug_dv (decl_or_value dv);
1409 DEBUG_FUNCTION void
1410 debug_dv (decl_or_value dv)
1412 if (dv_is_value_p (dv))
1413 debug_rtx (dv_as_value (dv));
1414 else
1415 debug_generic_stmt (dv_as_decl (dv));
1418 static void loc_exp_dep_clear (variable *var);
1420 /* Free the element of VARIABLE_HTAB (its type is struct variable_def). */
1422 static void
1423 variable_htab_free (void *elem)
1425 int i;
1426 variable *var = (variable *) elem;
1427 location_chain *node, *next;
1429 gcc_checking_assert (var->refcount > 0);
1431 var->refcount--;
1432 if (var->refcount > 0)
1433 return;
1435 for (i = 0; i < var->n_var_parts; i++)
1437 for (node = var->var_part[i].loc_chain; node; node = next)
1439 next = node->next;
1440 delete node;
1442 var->var_part[i].loc_chain = NULL;
1444 if (var->onepart && VAR_LOC_1PAUX (var))
1446 loc_exp_dep_clear (var);
1447 if (VAR_LOC_DEP_LST (var))
1448 VAR_LOC_DEP_LST (var)->pprev = NULL;
1449 XDELETE (VAR_LOC_1PAUX (var));
1450 /* These may be reused across functions, so reset
1451 e.g. NO_LOC_P. */
1452 if (var->onepart == ONEPART_DEXPR)
1453 set_dv_changed (var->dv, true);
1455 onepart_pool (var->onepart).remove (var);
1458 /* Initialize the set (array) SET of attrs to empty lists. */
1460 static void
1461 init_attrs_list_set (attrs **set)
1463 int i;
1465 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
1466 set[i] = NULL;
1469 /* Make the list *LISTP empty. */
1471 static void
1472 attrs_list_clear (attrs **listp)
1474 attrs *list, *next;
1476 for (list = *listp; list; list = next)
1478 next = list->next;
1479 delete list;
1481 *listp = NULL;
1484 /* Return true if the pair of DECL and OFFSET is the member of the LIST. */
1486 static attrs *
1487 attrs_list_member (attrs *list, decl_or_value dv, HOST_WIDE_INT offset)
1489 for (; list; list = list->next)
1490 if (dv_as_opaque (list->dv) == dv_as_opaque (dv) && list->offset == offset)
1491 return list;
1492 return NULL;
1495 /* Insert the triplet DECL, OFFSET, LOC to the list *LISTP. */
1497 static void
1498 attrs_list_insert (attrs **listp, decl_or_value dv,
1499 HOST_WIDE_INT offset, rtx loc)
1501 attrs *list = new attrs;
1502 list->loc = loc;
1503 list->dv = dv;
1504 list->offset = offset;
1505 list->next = *listp;
1506 *listp = list;
1509 /* Copy all nodes from SRC and create a list *DSTP of the copies. */
1511 static void
1512 attrs_list_copy (attrs **dstp, attrs *src)
1514 attrs_list_clear (dstp);
1515 for (; src; src = src->next)
1517 attrs *n = new attrs;
1518 n->loc = src->loc;
1519 n->dv = src->dv;
1520 n->offset = src->offset;
1521 n->next = *dstp;
1522 *dstp = n;
1526 /* Add all nodes from SRC which are not in *DSTP to *DSTP. */
1528 static void
1529 attrs_list_union (attrs **dstp, attrs *src)
1531 for (; src; src = src->next)
1533 if (!attrs_list_member (*dstp, src->dv, src->offset))
1534 attrs_list_insert (dstp, src->dv, src->offset, src->loc);
1538 /* Combine nodes that are not onepart nodes from SRC and SRC2 into
1539 *DSTP. */
1541 static void
1542 attrs_list_mpdv_union (attrs **dstp, attrs *src, attrs *src2)
1544 gcc_assert (!*dstp);
1545 for (; src; src = src->next)
1547 if (!dv_onepart_p (src->dv))
1548 attrs_list_insert (dstp, src->dv, src->offset, src->loc);
1550 for (src = src2; src; src = src->next)
1552 if (!dv_onepart_p (src->dv)
1553 && !attrs_list_member (*dstp, src->dv, src->offset))
1554 attrs_list_insert (dstp, src->dv, src->offset, src->loc);
1558 /* Shared hashtable support. */
1560 /* Return true if VARS is shared. */
1562 static inline bool
1563 shared_hash_shared (shared_hash *vars)
1565 return vars->refcount > 1;
1568 /* Return the hash table for VARS. */
1570 static inline variable_table_type *
1571 shared_hash_htab (shared_hash *vars)
1573 return vars->htab;
1576 /* Return true if VAR is shared, or maybe because VARS is shared. */
1578 static inline bool
1579 shared_var_p (variable *var, shared_hash *vars)
1581 /* Don't count an entry in the changed_variables table as a duplicate. */
1582 return ((var->refcount > 1 + (int) var->in_changed_variables)
1583 || shared_hash_shared (vars));
1586 /* Copy variables into a new hash table. */
1588 static shared_hash *
1589 shared_hash_unshare (shared_hash *vars)
1591 shared_hash *new_vars = new shared_hash;
1592 gcc_assert (vars->refcount > 1);
1593 new_vars->refcount = 1;
1594 new_vars->htab = new variable_table_type (vars->htab->elements () + 3);
1595 vars_copy (new_vars->htab, vars->htab);
1596 vars->refcount--;
1597 return new_vars;
1600 /* Increment reference counter on VARS and return it. */
1602 static inline shared_hash *
1603 shared_hash_copy (shared_hash *vars)
1605 vars->refcount++;
1606 return vars;
1609 /* Decrement reference counter and destroy hash table if not shared
1610 anymore. */
1612 static void
1613 shared_hash_destroy (shared_hash *vars)
1615 gcc_checking_assert (vars->refcount > 0);
1616 if (--vars->refcount == 0)
1618 delete vars->htab;
1619 delete vars;
1623 /* Unshare *PVARS if shared and return slot for DV. If INS is
1624 INSERT, insert it if not already present. */
1626 static inline variable **
1627 shared_hash_find_slot_unshare_1 (shared_hash **pvars, decl_or_value dv,
1628 hashval_t dvhash, enum insert_option ins)
1630 if (shared_hash_shared (*pvars))
1631 *pvars = shared_hash_unshare (*pvars);
1632 return shared_hash_htab (*pvars)->find_slot_with_hash (dv, dvhash, ins);
1635 static inline variable **
1636 shared_hash_find_slot_unshare (shared_hash **pvars, decl_or_value dv,
1637 enum insert_option ins)
1639 return shared_hash_find_slot_unshare_1 (pvars, dv, dv_htab_hash (dv), ins);
1642 /* Return slot for DV, if it is already present in the hash table.
1643 If it is not present, insert it only VARS is not shared, otherwise
1644 return NULL. */
1646 static inline variable **
1647 shared_hash_find_slot_1 (shared_hash *vars, decl_or_value dv, hashval_t dvhash)
1649 return shared_hash_htab (vars)->find_slot_with_hash (dv, dvhash,
1650 shared_hash_shared (vars)
1651 ? NO_INSERT : INSERT);
1654 static inline variable **
1655 shared_hash_find_slot (shared_hash *vars, decl_or_value dv)
1657 return shared_hash_find_slot_1 (vars, dv, dv_htab_hash (dv));
1660 /* Return slot for DV only if it is already present in the hash table. */
1662 static inline variable **
1663 shared_hash_find_slot_noinsert_1 (shared_hash *vars, decl_or_value dv,
1664 hashval_t dvhash)
1666 return shared_hash_htab (vars)->find_slot_with_hash (dv, dvhash, NO_INSERT);
1669 static inline variable **
1670 shared_hash_find_slot_noinsert (shared_hash *vars, decl_or_value dv)
1672 return shared_hash_find_slot_noinsert_1 (vars, dv, dv_htab_hash (dv));
1675 /* Return variable for DV or NULL if not already present in the hash
1676 table. */
1678 static inline variable *
1679 shared_hash_find_1 (shared_hash *vars, decl_or_value dv, hashval_t dvhash)
1681 return shared_hash_htab (vars)->find_with_hash (dv, dvhash);
1684 static inline variable *
1685 shared_hash_find (shared_hash *vars, decl_or_value dv)
1687 return shared_hash_find_1 (vars, dv, dv_htab_hash (dv));
1690 /* Return true if TVAL is better than CVAL as a canonival value. We
1691 choose lowest-numbered VALUEs, using the RTX address as a
1692 tie-breaker. The idea is to arrange them into a star topology,
1693 such that all of them are at most one step away from the canonical
1694 value, and the canonical value has backlinks to all of them, in
1695 addition to all the actual locations. We don't enforce this
1696 topology throughout the entire dataflow analysis, though.
1699 static inline bool
1700 canon_value_cmp (rtx tval, rtx cval)
1702 return !cval
1703 || CSELIB_VAL_PTR (tval)->uid < CSELIB_VAL_PTR (cval)->uid;
1706 static bool dst_can_be_shared;
1708 /* Return a copy of a variable VAR and insert it to dataflow set SET. */
1710 static variable **
1711 unshare_variable (dataflow_set *set, variable **slot, variable *var,
1712 enum var_init_status initialized)
1714 variable *new_var;
1715 int i;
1717 new_var = onepart_pool_allocate (var->onepart);
1718 new_var->dv = var->dv;
1719 new_var->refcount = 1;
1720 var->refcount--;
1721 new_var->n_var_parts = var->n_var_parts;
1722 new_var->onepart = var->onepart;
1723 new_var->in_changed_variables = false;
1725 if (! flag_var_tracking_uninit)
1726 initialized = VAR_INIT_STATUS_INITIALIZED;
1728 for (i = 0; i < var->n_var_parts; i++)
1730 location_chain *node;
1731 location_chain **nextp;
1733 if (i == 0 && var->onepart)
1735 /* One-part auxiliary data is only used while emitting
1736 notes, so propagate it to the new variable in the active
1737 dataflow set. If we're not emitting notes, this will be
1738 a no-op. */
1739 gcc_checking_assert (!VAR_LOC_1PAUX (var) || emit_notes);
1740 VAR_LOC_1PAUX (new_var) = VAR_LOC_1PAUX (var);
1741 VAR_LOC_1PAUX (var) = NULL;
1743 else
1744 VAR_PART_OFFSET (new_var, i) = VAR_PART_OFFSET (var, i);
1745 nextp = &new_var->var_part[i].loc_chain;
1746 for (node = var->var_part[i].loc_chain; node; node = node->next)
1748 location_chain *new_lc;
1750 new_lc = new location_chain;
1751 new_lc->next = NULL;
1752 if (node->init > initialized)
1753 new_lc->init = node->init;
1754 else
1755 new_lc->init = initialized;
1756 if (node->set_src && !(MEM_P (node->set_src)))
1757 new_lc->set_src = node->set_src;
1758 else
1759 new_lc->set_src = NULL;
1760 new_lc->loc = node->loc;
1762 *nextp = new_lc;
1763 nextp = &new_lc->next;
1766 new_var->var_part[i].cur_loc = var->var_part[i].cur_loc;
1769 dst_can_be_shared = false;
1770 if (shared_hash_shared (set->vars))
1771 slot = shared_hash_find_slot_unshare (&set->vars, var->dv, NO_INSERT);
1772 else if (set->traversed_vars && set->vars != set->traversed_vars)
1773 slot = shared_hash_find_slot_noinsert (set->vars, var->dv);
1774 *slot = new_var;
1775 if (var->in_changed_variables)
1777 variable **cslot
1778 = changed_variables->find_slot_with_hash (var->dv,
1779 dv_htab_hash (var->dv),
1780 NO_INSERT);
1781 gcc_assert (*cslot == (void *) var);
1782 var->in_changed_variables = false;
1783 variable_htab_free (var);
1784 *cslot = new_var;
1785 new_var->in_changed_variables = true;
1787 return slot;
1790 /* Copy all variables from hash table SRC to hash table DST. */
1792 static void
1793 vars_copy (variable_table_type *dst, variable_table_type *src)
1795 variable_iterator_type hi;
1796 variable *var;
1798 FOR_EACH_HASH_TABLE_ELEMENT (*src, var, variable, hi)
1800 variable **dstp;
1801 var->refcount++;
1802 dstp = dst->find_slot_with_hash (var->dv, dv_htab_hash (var->dv),
1803 INSERT);
1804 *dstp = var;
1808 /* Map a decl to its main debug decl. */
1810 static inline tree
1811 var_debug_decl (tree decl)
1813 if (decl && VAR_P (decl) && DECL_HAS_DEBUG_EXPR_P (decl))
1815 tree debugdecl = DECL_DEBUG_EXPR (decl);
1816 if (DECL_P (debugdecl))
1817 decl = debugdecl;
1820 return decl;
1823 /* Set the register LOC to contain DV, OFFSET. */
1825 static void
1826 var_reg_decl_set (dataflow_set *set, rtx loc, enum var_init_status initialized,
1827 decl_or_value dv, HOST_WIDE_INT offset, rtx set_src,
1828 enum insert_option iopt)
1830 attrs *node;
1831 bool decl_p = dv_is_decl_p (dv);
1833 if (decl_p)
1834 dv = dv_from_decl (var_debug_decl (dv_as_decl (dv)));
1836 for (node = set->regs[REGNO (loc)]; node; node = node->next)
1837 if (dv_as_opaque (node->dv) == dv_as_opaque (dv)
1838 && node->offset == offset)
1839 break;
1840 if (!node)
1841 attrs_list_insert (&set->regs[REGNO (loc)], dv, offset, loc);
1842 set_variable_part (set, loc, dv, offset, initialized, set_src, iopt);
1845 /* Set the register to contain REG_EXPR (LOC), REG_OFFSET (LOC). */
1847 static void
1848 var_reg_set (dataflow_set *set, rtx loc, enum var_init_status initialized,
1849 rtx set_src)
1851 tree decl = REG_EXPR (loc);
1852 HOST_WIDE_INT offset = REG_OFFSET (loc);
1854 var_reg_decl_set (set, loc, initialized,
1855 dv_from_decl (decl), offset, set_src, INSERT);
1858 static enum var_init_status
1859 get_init_value (dataflow_set *set, rtx loc, decl_or_value dv)
1861 variable *var;
1862 int i;
1863 enum var_init_status ret_val = VAR_INIT_STATUS_UNKNOWN;
1865 if (! flag_var_tracking_uninit)
1866 return VAR_INIT_STATUS_INITIALIZED;
1868 var = shared_hash_find (set->vars, dv);
1869 if (var)
1871 for (i = 0; i < var->n_var_parts && ret_val == VAR_INIT_STATUS_UNKNOWN; i++)
1873 location_chain *nextp;
1874 for (nextp = var->var_part[i].loc_chain; nextp; nextp = nextp->next)
1875 if (rtx_equal_p (nextp->loc, loc))
1877 ret_val = nextp->init;
1878 break;
1883 return ret_val;
1886 /* Delete current content of register LOC in dataflow set SET and set
1887 the register to contain REG_EXPR (LOC), REG_OFFSET (LOC). If
1888 MODIFY is true, any other live copies of the same variable part are
1889 also deleted from the dataflow set, otherwise the variable part is
1890 assumed to be copied from another location holding the same
1891 part. */
1893 static void
1894 var_reg_delete_and_set (dataflow_set *set, rtx loc, bool modify,
1895 enum var_init_status initialized, rtx set_src)
1897 tree decl = REG_EXPR (loc);
1898 HOST_WIDE_INT offset = REG_OFFSET (loc);
1899 attrs *node, *next;
1900 attrs **nextp;
1902 decl = var_debug_decl (decl);
1904 if (initialized == VAR_INIT_STATUS_UNKNOWN)
1905 initialized = get_init_value (set, loc, dv_from_decl (decl));
1907 nextp = &set->regs[REGNO (loc)];
1908 for (node = *nextp; node; node = next)
1910 next = node->next;
1911 if (dv_as_opaque (node->dv) != decl || node->offset != offset)
1913 delete_variable_part (set, node->loc, node->dv, node->offset);
1914 delete node;
1915 *nextp = next;
1917 else
1919 node->loc = loc;
1920 nextp = &node->next;
1923 if (modify)
1924 clobber_variable_part (set, loc, dv_from_decl (decl), offset, set_src);
1925 var_reg_set (set, loc, initialized, set_src);
1928 /* Delete the association of register LOC in dataflow set SET with any
1929 variables that aren't onepart. If CLOBBER is true, also delete any
1930 other live copies of the same variable part, and delete the
1931 association with onepart dvs too. */
1933 static void
1934 var_reg_delete (dataflow_set *set, rtx loc, bool clobber)
1936 attrs **nextp = &set->regs[REGNO (loc)];
1937 attrs *node, *next;
1939 if (clobber)
1941 tree decl = REG_EXPR (loc);
1942 HOST_WIDE_INT offset = REG_OFFSET (loc);
1944 decl = var_debug_decl (decl);
1946 clobber_variable_part (set, NULL, dv_from_decl (decl), offset, NULL);
1949 for (node = *nextp; node; node = next)
1951 next = node->next;
1952 if (clobber || !dv_onepart_p (node->dv))
1954 delete_variable_part (set, node->loc, node->dv, node->offset);
1955 delete node;
1956 *nextp = next;
1958 else
1959 nextp = &node->next;
1963 /* Delete content of register with number REGNO in dataflow set SET. */
1965 static void
1966 var_regno_delete (dataflow_set *set, int regno)
1968 attrs **reg = &set->regs[regno];
1969 attrs *node, *next;
1971 for (node = *reg; node; node = next)
1973 next = node->next;
1974 delete_variable_part (set, node->loc, node->dv, node->offset);
1975 delete node;
1977 *reg = NULL;
1980 /* Return true if I is the negated value of a power of two. */
1981 static bool
1982 negative_power_of_two_p (HOST_WIDE_INT i)
1984 unsigned HOST_WIDE_INT x = -(unsigned HOST_WIDE_INT)i;
1985 return pow2_or_zerop (x);
1988 /* Strip constant offsets and alignments off of LOC. Return the base
1989 expression. */
1991 static rtx
1992 vt_get_canonicalize_base (rtx loc)
1994 while ((GET_CODE (loc) == PLUS
1995 || GET_CODE (loc) == AND)
1996 && GET_CODE (XEXP (loc, 1)) == CONST_INT
1997 && (GET_CODE (loc) != AND
1998 || negative_power_of_two_p (INTVAL (XEXP (loc, 1)))))
1999 loc = XEXP (loc, 0);
2001 return loc;
2004 /* This caches canonicalized addresses for VALUEs, computed using
2005 information in the global cselib table. */
2006 static hash_map<rtx, rtx> *global_get_addr_cache;
2008 /* This caches canonicalized addresses for VALUEs, computed using
2009 information from the global cache and information pertaining to a
2010 basic block being analyzed. */
2011 static hash_map<rtx, rtx> *local_get_addr_cache;
2013 static rtx vt_canonicalize_addr (dataflow_set *, rtx);
2015 /* Return the canonical address for LOC, that must be a VALUE, using a
2016 cached global equivalence or computing it and storing it in the
2017 global cache. */
2019 static rtx
2020 get_addr_from_global_cache (rtx const loc)
2022 rtx x;
2024 gcc_checking_assert (GET_CODE (loc) == VALUE);
2026 bool existed;
2027 rtx *slot = &global_get_addr_cache->get_or_insert (loc, &existed);
2028 if (existed)
2029 return *slot;
2031 x = canon_rtx (get_addr (loc));
2033 /* Tentative, avoiding infinite recursion. */
2034 *slot = x;
2036 if (x != loc)
2038 rtx nx = vt_canonicalize_addr (NULL, x);
2039 if (nx != x)
2041 /* The table may have moved during recursion, recompute
2042 SLOT. */
2043 *global_get_addr_cache->get (loc) = x = nx;
2047 return x;
2050 /* Return the canonical address for LOC, that must be a VALUE, using a
2051 cached local equivalence or computing it and storing it in the
2052 local cache. */
2054 static rtx
2055 get_addr_from_local_cache (dataflow_set *set, rtx const loc)
2057 rtx x;
2058 decl_or_value dv;
2059 variable *var;
2060 location_chain *l;
2062 gcc_checking_assert (GET_CODE (loc) == VALUE);
2064 bool existed;
2065 rtx *slot = &local_get_addr_cache->get_or_insert (loc, &existed);
2066 if (existed)
2067 return *slot;
2069 x = get_addr_from_global_cache (loc);
2071 /* Tentative, avoiding infinite recursion. */
2072 *slot = x;
2074 /* Recurse to cache local expansion of X, or if we need to search
2075 for a VALUE in the expansion. */
2076 if (x != loc)
2078 rtx nx = vt_canonicalize_addr (set, x);
2079 if (nx != x)
2081 slot = local_get_addr_cache->get (loc);
2082 *slot = x = nx;
2084 return x;
2087 dv = dv_from_rtx (x);
2088 var = shared_hash_find (set->vars, dv);
2089 if (!var)
2090 return x;
2092 /* Look for an improved equivalent expression. */
2093 for (l = var->var_part[0].loc_chain; l; l = l->next)
2095 rtx base = vt_get_canonicalize_base (l->loc);
2096 if (GET_CODE (base) == VALUE
2097 && canon_value_cmp (base, loc))
2099 rtx nx = vt_canonicalize_addr (set, l->loc);
2100 if (x != nx)
2102 slot = local_get_addr_cache->get (loc);
2103 *slot = x = nx;
2105 break;
2109 return x;
2112 /* Canonicalize LOC using equivalences from SET in addition to those
2113 in the cselib static table. It expects a VALUE-based expression,
2114 and it will only substitute VALUEs with other VALUEs or
2115 function-global equivalences, so that, if two addresses have base
2116 VALUEs that are locally or globally related in ways that
2117 memrefs_conflict_p cares about, they will both canonicalize to
2118 expressions that have the same base VALUE.
2120 The use of VALUEs as canonical base addresses enables the canonical
2121 RTXs to remain unchanged globally, if they resolve to a constant,
2122 or throughout a basic block otherwise, so that they can be cached
2123 and the cache needs not be invalidated when REGs, MEMs or such
2124 change. */
2126 static rtx
2127 vt_canonicalize_addr (dataflow_set *set, rtx oloc)
2129 HOST_WIDE_INT ofst = 0;
2130 machine_mode mode = GET_MODE (oloc);
2131 rtx loc = oloc;
2132 rtx x;
2133 bool retry = true;
2135 while (retry)
2137 while (GET_CODE (loc) == PLUS
2138 && GET_CODE (XEXP (loc, 1)) == CONST_INT)
2140 ofst += INTVAL (XEXP (loc, 1));
2141 loc = XEXP (loc, 0);
2144 /* Alignment operations can't normally be combined, so just
2145 canonicalize the base and we're done. We'll normally have
2146 only one stack alignment anyway. */
2147 if (GET_CODE (loc) == AND
2148 && GET_CODE (XEXP (loc, 1)) == CONST_INT
2149 && negative_power_of_two_p (INTVAL (XEXP (loc, 1))))
2151 x = vt_canonicalize_addr (set, XEXP (loc, 0));
2152 if (x != XEXP (loc, 0))
2153 loc = gen_rtx_AND (mode, x, XEXP (loc, 1));
2154 retry = false;
2157 if (GET_CODE (loc) == VALUE)
2159 if (set)
2160 loc = get_addr_from_local_cache (set, loc);
2161 else
2162 loc = get_addr_from_global_cache (loc);
2164 /* Consolidate plus_constants. */
2165 while (ofst && GET_CODE (loc) == PLUS
2166 && GET_CODE (XEXP (loc, 1)) == CONST_INT)
2168 ofst += INTVAL (XEXP (loc, 1));
2169 loc = XEXP (loc, 0);
2172 retry = false;
2174 else
2176 x = canon_rtx (loc);
2177 if (retry)
2178 retry = (x != loc);
2179 loc = x;
2183 /* Add OFST back in. */
2184 if (ofst)
2186 /* Don't build new RTL if we can help it. */
2187 if (GET_CODE (oloc) == PLUS
2188 && XEXP (oloc, 0) == loc
2189 && INTVAL (XEXP (oloc, 1)) == ofst)
2190 return oloc;
2192 loc = plus_constant (mode, loc, ofst);
2195 return loc;
2198 /* Return true iff there's a true dependence between MLOC and LOC.
2199 MADDR must be a canonicalized version of MLOC's address. */
2201 static inline bool
2202 vt_canon_true_dep (dataflow_set *set, rtx mloc, rtx maddr, rtx loc)
2204 if (GET_CODE (loc) != MEM)
2205 return false;
2207 rtx addr = vt_canonicalize_addr (set, XEXP (loc, 0));
2208 if (!canon_true_dependence (mloc, GET_MODE (mloc), maddr, loc, addr))
2209 return false;
2211 return true;
2214 /* Hold parameters for the hashtab traversal function
2215 drop_overlapping_mem_locs, see below. */
2217 struct overlapping_mems
2219 dataflow_set *set;
2220 rtx loc, addr;
2223 /* Remove all MEMs that overlap with COMS->LOC from the location list
2224 of a hash table entry for a onepart variable. COMS->ADDR must be a
2225 canonicalized form of COMS->LOC's address, and COMS->LOC must be
2226 canonicalized itself. */
2229 drop_overlapping_mem_locs (variable **slot, overlapping_mems *coms)
2231 dataflow_set *set = coms->set;
2232 rtx mloc = coms->loc, addr = coms->addr;
2233 variable *var = *slot;
2235 if (var->onepart != NOT_ONEPART)
2237 location_chain *loc, **locp;
2238 bool changed = false;
2239 rtx cur_loc;
2241 gcc_assert (var->n_var_parts == 1);
2243 if (shared_var_p (var, set->vars))
2245 for (loc = var->var_part[0].loc_chain; loc; loc = loc->next)
2246 if (vt_canon_true_dep (set, mloc, addr, loc->loc))
2247 break;
2249 if (!loc)
2250 return 1;
2252 slot = unshare_variable (set, slot, var, VAR_INIT_STATUS_UNKNOWN);
2253 var = *slot;
2254 gcc_assert (var->n_var_parts == 1);
2257 if (VAR_LOC_1PAUX (var))
2258 cur_loc = VAR_LOC_FROM (var);
2259 else
2260 cur_loc = var->var_part[0].cur_loc;
2262 for (locp = &var->var_part[0].loc_chain, loc = *locp;
2263 loc; loc = *locp)
2265 if (!vt_canon_true_dep (set, mloc, addr, loc->loc))
2267 locp = &loc->next;
2268 continue;
2271 *locp = loc->next;
2272 /* If we have deleted the location which was last emitted
2273 we have to emit new location so add the variable to set
2274 of changed variables. */
2275 if (cur_loc == loc->loc)
2277 changed = true;
2278 var->var_part[0].cur_loc = NULL;
2279 if (VAR_LOC_1PAUX (var))
2280 VAR_LOC_FROM (var) = NULL;
2282 delete loc;
2285 if (!var->var_part[0].loc_chain)
2287 var->n_var_parts--;
2288 changed = true;
2290 if (changed)
2291 variable_was_changed (var, set);
2294 return 1;
2297 /* Remove from SET all VALUE bindings to MEMs that overlap with LOC. */
2299 static void
2300 clobber_overlapping_mems (dataflow_set *set, rtx loc)
2302 struct overlapping_mems coms;
2304 gcc_checking_assert (GET_CODE (loc) == MEM);
2306 coms.set = set;
2307 coms.loc = canon_rtx (loc);
2308 coms.addr = vt_canonicalize_addr (set, XEXP (loc, 0));
2310 set->traversed_vars = set->vars;
2311 shared_hash_htab (set->vars)
2312 ->traverse <overlapping_mems*, drop_overlapping_mem_locs> (&coms);
2313 set->traversed_vars = NULL;
2316 /* Set the location of DV, OFFSET as the MEM LOC. */
2318 static void
2319 var_mem_decl_set (dataflow_set *set, rtx loc, enum var_init_status initialized,
2320 decl_or_value dv, HOST_WIDE_INT offset, rtx set_src,
2321 enum insert_option iopt)
2323 if (dv_is_decl_p (dv))
2324 dv = dv_from_decl (var_debug_decl (dv_as_decl (dv)));
2326 set_variable_part (set, loc, dv, offset, initialized, set_src, iopt);
2329 /* Set the location part of variable MEM_EXPR (LOC) in dataflow set
2330 SET to LOC.
2331 Adjust the address first if it is stack pointer based. */
2333 static void
2334 var_mem_set (dataflow_set *set, rtx loc, enum var_init_status initialized,
2335 rtx set_src)
2337 tree decl = MEM_EXPR (loc);
2338 HOST_WIDE_INT offset = INT_MEM_OFFSET (loc);
2340 var_mem_decl_set (set, loc, initialized,
2341 dv_from_decl (decl), offset, set_src, INSERT);
2344 /* Delete and set the location part of variable MEM_EXPR (LOC) in
2345 dataflow set SET to LOC. If MODIFY is true, any other live copies
2346 of the same variable part are also deleted from the dataflow set,
2347 otherwise the variable part is assumed to be copied from another
2348 location holding the same part.
2349 Adjust the address first if it is stack pointer based. */
2351 static void
2352 var_mem_delete_and_set (dataflow_set *set, rtx loc, bool modify,
2353 enum var_init_status initialized, rtx set_src)
2355 tree decl = MEM_EXPR (loc);
2356 HOST_WIDE_INT offset = INT_MEM_OFFSET (loc);
2358 clobber_overlapping_mems (set, loc);
2359 decl = var_debug_decl (decl);
2361 if (initialized == VAR_INIT_STATUS_UNKNOWN)
2362 initialized = get_init_value (set, loc, dv_from_decl (decl));
2364 if (modify)
2365 clobber_variable_part (set, NULL, dv_from_decl (decl), offset, set_src);
2366 var_mem_set (set, loc, initialized, set_src);
2369 /* Delete the location part LOC from dataflow set SET. If CLOBBER is
2370 true, also delete any other live copies of the same variable part.
2371 Adjust the address first if it is stack pointer based. */
2373 static void
2374 var_mem_delete (dataflow_set *set, rtx loc, bool clobber)
2376 tree decl = MEM_EXPR (loc);
2377 HOST_WIDE_INT offset = INT_MEM_OFFSET (loc);
2379 clobber_overlapping_mems (set, loc);
2380 decl = var_debug_decl (decl);
2381 if (clobber)
2382 clobber_variable_part (set, NULL, dv_from_decl (decl), offset, NULL);
2383 delete_variable_part (set, loc, dv_from_decl (decl), offset);
2386 /* Return true if LOC should not be expanded for location expressions,
2387 or used in them. */
2389 static inline bool
2390 unsuitable_loc (rtx loc)
2392 switch (GET_CODE (loc))
2394 case PC:
2395 case SCRATCH:
2396 case CC0:
2397 case ASM_INPUT:
2398 case ASM_OPERANDS:
2399 return true;
2401 default:
2402 return false;
2406 /* Bind VAL to LOC in SET. If MODIFIED, detach LOC from any values
2407 bound to it. */
2409 static inline void
2410 val_bind (dataflow_set *set, rtx val, rtx loc, bool modified)
2412 if (REG_P (loc))
2414 if (modified)
2415 var_regno_delete (set, REGNO (loc));
2416 var_reg_decl_set (set, loc, VAR_INIT_STATUS_INITIALIZED,
2417 dv_from_value (val), 0, NULL_RTX, INSERT);
2419 else if (MEM_P (loc))
2421 struct elt_loc_list *l = CSELIB_VAL_PTR (val)->locs;
2423 if (modified)
2424 clobber_overlapping_mems (set, loc);
2426 if (l && GET_CODE (l->loc) == VALUE)
2427 l = canonical_cselib_val (CSELIB_VAL_PTR (l->loc))->locs;
2429 /* If this MEM is a global constant, we don't need it in the
2430 dynamic tables. ??? We should test this before emitting the
2431 micro-op in the first place. */
2432 while (l)
2433 if (GET_CODE (l->loc) == MEM && XEXP (l->loc, 0) == XEXP (loc, 0))
2434 break;
2435 else
2436 l = l->next;
2438 if (!l)
2439 var_mem_decl_set (set, loc, VAR_INIT_STATUS_INITIALIZED,
2440 dv_from_value (val), 0, NULL_RTX, INSERT);
2442 else
2444 /* Other kinds of equivalences are necessarily static, at least
2445 so long as we do not perform substitutions while merging
2446 expressions. */
2447 gcc_unreachable ();
2448 set_variable_part (set, loc, dv_from_value (val), 0,
2449 VAR_INIT_STATUS_INITIALIZED, NULL_RTX, INSERT);
2453 /* Bind a value to a location it was just stored in. If MODIFIED
2454 holds, assume the location was modified, detaching it from any
2455 values bound to it. */
2457 static void
2458 val_store (dataflow_set *set, rtx val, rtx loc, rtx_insn *insn,
2459 bool modified)
2461 cselib_val *v = CSELIB_VAL_PTR (val);
2463 gcc_assert (cselib_preserved_value_p (v));
2465 if (dump_file)
2467 fprintf (dump_file, "%i: ", insn ? INSN_UID (insn) : 0);
2468 print_inline_rtx (dump_file, loc, 0);
2469 fprintf (dump_file, " evaluates to ");
2470 print_inline_rtx (dump_file, val, 0);
2471 if (v->locs)
2473 struct elt_loc_list *l;
2474 for (l = v->locs; l; l = l->next)
2476 fprintf (dump_file, "\n%i: ", INSN_UID (l->setting_insn));
2477 print_inline_rtx (dump_file, l->loc, 0);
2480 fprintf (dump_file, "\n");
2483 gcc_checking_assert (!unsuitable_loc (loc));
2485 val_bind (set, val, loc, modified);
2488 /* Clear (canonical address) slots that reference X. */
2490 bool
2491 local_get_addr_clear_given_value (rtx const &, rtx *slot, rtx x)
2493 if (vt_get_canonicalize_base (*slot) == x)
2494 *slot = NULL;
2495 return true;
2498 /* Reset this node, detaching all its equivalences. Return the slot
2499 in the variable hash table that holds dv, if there is one. */
2501 static void
2502 val_reset (dataflow_set *set, decl_or_value dv)
2504 variable *var = shared_hash_find (set->vars, dv) ;
2505 location_chain *node;
2506 rtx cval;
2508 if (!var || !var->n_var_parts)
2509 return;
2511 gcc_assert (var->n_var_parts == 1);
2513 if (var->onepart == ONEPART_VALUE)
2515 rtx x = dv_as_value (dv);
2517 /* Relationships in the global cache don't change, so reset the
2518 local cache entry only. */
2519 rtx *slot = local_get_addr_cache->get (x);
2520 if (slot)
2522 /* If the value resolved back to itself, odds are that other
2523 values may have cached it too. These entries now refer
2524 to the old X, so detach them too. Entries that used the
2525 old X but resolved to something else remain ok as long as
2526 that something else isn't also reset. */
2527 if (*slot == x)
2528 local_get_addr_cache
2529 ->traverse<rtx, local_get_addr_clear_given_value> (x);
2530 *slot = NULL;
2534 cval = NULL;
2535 for (node = var->var_part[0].loc_chain; node; node = node->next)
2536 if (GET_CODE (node->loc) == VALUE
2537 && canon_value_cmp (node->loc, cval))
2538 cval = node->loc;
2540 for (node = var->var_part[0].loc_chain; node; node = node->next)
2541 if (GET_CODE (node->loc) == VALUE && cval != node->loc)
2543 /* Redirect the equivalence link to the new canonical
2544 value, or simply remove it if it would point at
2545 itself. */
2546 if (cval)
2547 set_variable_part (set, cval, dv_from_value (node->loc),
2548 0, node->init, node->set_src, NO_INSERT);
2549 delete_variable_part (set, dv_as_value (dv),
2550 dv_from_value (node->loc), 0);
2553 if (cval)
2555 decl_or_value cdv = dv_from_value (cval);
2557 /* Keep the remaining values connected, accummulating links
2558 in the canonical value. */
2559 for (node = var->var_part[0].loc_chain; node; node = node->next)
2561 if (node->loc == cval)
2562 continue;
2563 else if (GET_CODE (node->loc) == REG)
2564 var_reg_decl_set (set, node->loc, node->init, cdv, 0,
2565 node->set_src, NO_INSERT);
2566 else if (GET_CODE (node->loc) == MEM)
2567 var_mem_decl_set (set, node->loc, node->init, cdv, 0,
2568 node->set_src, NO_INSERT);
2569 else
2570 set_variable_part (set, node->loc, cdv, 0,
2571 node->init, node->set_src, NO_INSERT);
2575 /* We remove this last, to make sure that the canonical value is not
2576 removed to the point of requiring reinsertion. */
2577 if (cval)
2578 delete_variable_part (set, dv_as_value (dv), dv_from_value (cval), 0);
2580 clobber_variable_part (set, NULL, dv, 0, NULL);
2583 /* Find the values in a given location and map the val to another
2584 value, if it is unique, or add the location as one holding the
2585 value. */
2587 static void
2588 val_resolve (dataflow_set *set, rtx val, rtx loc, rtx_insn *insn)
2590 decl_or_value dv = dv_from_value (val);
2592 if (dump_file && (dump_flags & TDF_DETAILS))
2594 if (insn)
2595 fprintf (dump_file, "%i: ", INSN_UID (insn));
2596 else
2597 fprintf (dump_file, "head: ");
2598 print_inline_rtx (dump_file, val, 0);
2599 fputs (" is at ", dump_file);
2600 print_inline_rtx (dump_file, loc, 0);
2601 fputc ('\n', dump_file);
2604 val_reset (set, dv);
2606 gcc_checking_assert (!unsuitable_loc (loc));
2608 if (REG_P (loc))
2610 attrs *node, *found = NULL;
2612 for (node = set->regs[REGNO (loc)]; node; node = node->next)
2613 if (dv_is_value_p (node->dv)
2614 && GET_MODE (dv_as_value (node->dv)) == GET_MODE (loc))
2616 found = node;
2618 /* Map incoming equivalences. ??? Wouldn't it be nice if
2619 we just started sharing the location lists? Maybe a
2620 circular list ending at the value itself or some
2621 such. */
2622 set_variable_part (set, dv_as_value (node->dv),
2623 dv_from_value (val), node->offset,
2624 VAR_INIT_STATUS_INITIALIZED, NULL_RTX, INSERT);
2625 set_variable_part (set, val, node->dv, node->offset,
2626 VAR_INIT_STATUS_INITIALIZED, NULL_RTX, INSERT);
2629 /* If we didn't find any equivalence, we need to remember that
2630 this value is held in the named register. */
2631 if (found)
2632 return;
2634 /* ??? Attempt to find and merge equivalent MEMs or other
2635 expressions too. */
2637 val_bind (set, val, loc, false);
2640 /* Initialize dataflow set SET to be empty.
2641 VARS_SIZE is the initial size of hash table VARS. */
2643 static void
2644 dataflow_set_init (dataflow_set *set)
2646 init_attrs_list_set (set->regs);
2647 set->vars = shared_hash_copy (empty_shared_hash);
2648 set->stack_adjust = 0;
2649 set->traversed_vars = NULL;
2652 /* Delete the contents of dataflow set SET. */
2654 static void
2655 dataflow_set_clear (dataflow_set *set)
2657 int i;
2659 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
2660 attrs_list_clear (&set->regs[i]);
2662 shared_hash_destroy (set->vars);
2663 set->vars = shared_hash_copy (empty_shared_hash);
2666 /* Copy the contents of dataflow set SRC to DST. */
2668 static void
2669 dataflow_set_copy (dataflow_set *dst, dataflow_set *src)
2671 int i;
2673 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
2674 attrs_list_copy (&dst->regs[i], src->regs[i]);
2676 shared_hash_destroy (dst->vars);
2677 dst->vars = shared_hash_copy (src->vars);
2678 dst->stack_adjust = src->stack_adjust;
2681 /* Information for merging lists of locations for a given offset of variable.
2683 struct variable_union_info
2685 /* Node of the location chain. */
2686 location_chain *lc;
2688 /* The sum of positions in the input chains. */
2689 int pos;
2691 /* The position in the chain of DST dataflow set. */
2692 int pos_dst;
2695 /* Buffer for location list sorting and its allocated size. */
2696 static struct variable_union_info *vui_vec;
2697 static int vui_allocated;
2699 /* Compare function for qsort, order the structures by POS element. */
2701 static int
2702 variable_union_info_cmp_pos (const void *n1, const void *n2)
2704 const struct variable_union_info *const i1 =
2705 (const struct variable_union_info *) n1;
2706 const struct variable_union_info *const i2 =
2707 ( const struct variable_union_info *) n2;
2709 if (i1->pos != i2->pos)
2710 return i1->pos - i2->pos;
2712 return (i1->pos_dst - i2->pos_dst);
2715 /* Compute union of location parts of variable *SLOT and the same variable
2716 from hash table DATA. Compute "sorted" union of the location chains
2717 for common offsets, i.e. the locations of a variable part are sorted by
2718 a priority where the priority is the sum of the positions in the 2 chains
2719 (if a location is only in one list the position in the second list is
2720 defined to be larger than the length of the chains).
2721 When we are updating the location parts the newest location is in the
2722 beginning of the chain, so when we do the described "sorted" union
2723 we keep the newest locations in the beginning. */
2725 static int
2726 variable_union (variable *src, dataflow_set *set)
2728 variable *dst;
2729 variable **dstp;
2730 int i, j, k;
2732 dstp = shared_hash_find_slot (set->vars, src->dv);
2733 if (!dstp || !*dstp)
2735 src->refcount++;
2737 dst_can_be_shared = false;
2738 if (!dstp)
2739 dstp = shared_hash_find_slot_unshare (&set->vars, src->dv, INSERT);
2741 *dstp = src;
2743 /* Continue traversing the hash table. */
2744 return 1;
2746 else
2747 dst = *dstp;
2749 gcc_assert (src->n_var_parts);
2750 gcc_checking_assert (src->onepart == dst->onepart);
2752 /* We can combine one-part variables very efficiently, because their
2753 entries are in canonical order. */
2754 if (src->onepart)
2756 location_chain **nodep, *dnode, *snode;
2758 gcc_assert (src->n_var_parts == 1
2759 && dst->n_var_parts == 1);
2761 snode = src->var_part[0].loc_chain;
2762 gcc_assert (snode);
2764 restart_onepart_unshared:
2765 nodep = &dst->var_part[0].loc_chain;
2766 dnode = *nodep;
2767 gcc_assert (dnode);
2769 while (snode)
2771 int r = dnode ? loc_cmp (dnode->loc, snode->loc) : 1;
2773 if (r > 0)
2775 location_chain *nnode;
2777 if (shared_var_p (dst, set->vars))
2779 dstp = unshare_variable (set, dstp, dst,
2780 VAR_INIT_STATUS_INITIALIZED);
2781 dst = *dstp;
2782 goto restart_onepart_unshared;
2785 *nodep = nnode = new location_chain;
2786 nnode->loc = snode->loc;
2787 nnode->init = snode->init;
2788 if (!snode->set_src || MEM_P (snode->set_src))
2789 nnode->set_src = NULL;
2790 else
2791 nnode->set_src = snode->set_src;
2792 nnode->next = dnode;
2793 dnode = nnode;
2795 else if (r == 0)
2796 gcc_checking_assert (rtx_equal_p (dnode->loc, snode->loc));
2798 if (r >= 0)
2799 snode = snode->next;
2801 nodep = &dnode->next;
2802 dnode = *nodep;
2805 return 1;
2808 gcc_checking_assert (!src->onepart);
2810 /* Count the number of location parts, result is K. */
2811 for (i = 0, j = 0, k = 0;
2812 i < src->n_var_parts && j < dst->n_var_parts; k++)
2814 if (VAR_PART_OFFSET (src, i) == VAR_PART_OFFSET (dst, j))
2816 i++;
2817 j++;
2819 else if (VAR_PART_OFFSET (src, i) < VAR_PART_OFFSET (dst, j))
2820 i++;
2821 else
2822 j++;
2824 k += src->n_var_parts - i;
2825 k += dst->n_var_parts - j;
2827 /* We track only variables whose size is <= MAX_VAR_PARTS bytes
2828 thus there are at most MAX_VAR_PARTS different offsets. */
2829 gcc_checking_assert (dst->onepart ? k == 1 : k <= MAX_VAR_PARTS);
2831 if (dst->n_var_parts != k && shared_var_p (dst, set->vars))
2833 dstp = unshare_variable (set, dstp, dst, VAR_INIT_STATUS_UNKNOWN);
2834 dst = *dstp;
2837 i = src->n_var_parts - 1;
2838 j = dst->n_var_parts - 1;
2839 dst->n_var_parts = k;
2841 for (k--; k >= 0; k--)
2843 location_chain *node, *node2;
2845 if (i >= 0 && j >= 0
2846 && VAR_PART_OFFSET (src, i) == VAR_PART_OFFSET (dst, j))
2848 /* Compute the "sorted" union of the chains, i.e. the locations which
2849 are in both chains go first, they are sorted by the sum of
2850 positions in the chains. */
2851 int dst_l, src_l;
2852 int ii, jj, n;
2853 struct variable_union_info *vui;
2855 /* If DST is shared compare the location chains.
2856 If they are different we will modify the chain in DST with
2857 high probability so make a copy of DST. */
2858 if (shared_var_p (dst, set->vars))
2860 for (node = src->var_part[i].loc_chain,
2861 node2 = dst->var_part[j].loc_chain; node && node2;
2862 node = node->next, node2 = node2->next)
2864 if (!((REG_P (node2->loc)
2865 && REG_P (node->loc)
2866 && REGNO (node2->loc) == REGNO (node->loc))
2867 || rtx_equal_p (node2->loc, node->loc)))
2869 if (node2->init < node->init)
2870 node2->init = node->init;
2871 break;
2874 if (node || node2)
2876 dstp = unshare_variable (set, dstp, dst,
2877 VAR_INIT_STATUS_UNKNOWN);
2878 dst = (variable *)*dstp;
2882 src_l = 0;
2883 for (node = src->var_part[i].loc_chain; node; node = node->next)
2884 src_l++;
2885 dst_l = 0;
2886 for (node = dst->var_part[j].loc_chain; node; node = node->next)
2887 dst_l++;
2889 if (dst_l == 1)
2891 /* The most common case, much simpler, no qsort is needed. */
2892 location_chain *dstnode = dst->var_part[j].loc_chain;
2893 dst->var_part[k].loc_chain = dstnode;
2894 VAR_PART_OFFSET (dst, k) = VAR_PART_OFFSET (dst, j);
2895 node2 = dstnode;
2896 for (node = src->var_part[i].loc_chain; node; node = node->next)
2897 if (!((REG_P (dstnode->loc)
2898 && REG_P (node->loc)
2899 && REGNO (dstnode->loc) == REGNO (node->loc))
2900 || rtx_equal_p (dstnode->loc, node->loc)))
2902 location_chain *new_node;
2904 /* Copy the location from SRC. */
2905 new_node = new location_chain;
2906 new_node->loc = node->loc;
2907 new_node->init = node->init;
2908 if (!node->set_src || MEM_P (node->set_src))
2909 new_node->set_src = NULL;
2910 else
2911 new_node->set_src = node->set_src;
2912 node2->next = new_node;
2913 node2 = new_node;
2915 node2->next = NULL;
2917 else
2919 if (src_l + dst_l > vui_allocated)
2921 vui_allocated = MAX (vui_allocated * 2, src_l + dst_l);
2922 vui_vec = XRESIZEVEC (struct variable_union_info, vui_vec,
2923 vui_allocated);
2925 vui = vui_vec;
2927 /* Fill in the locations from DST. */
2928 for (node = dst->var_part[j].loc_chain, jj = 0; node;
2929 node = node->next, jj++)
2931 vui[jj].lc = node;
2932 vui[jj].pos_dst = jj;
2934 /* Pos plus value larger than a sum of 2 valid positions. */
2935 vui[jj].pos = jj + src_l + dst_l;
2938 /* Fill in the locations from SRC. */
2939 n = dst_l;
2940 for (node = src->var_part[i].loc_chain, ii = 0; node;
2941 node = node->next, ii++)
2943 /* Find location from NODE. */
2944 for (jj = 0; jj < dst_l; jj++)
2946 if ((REG_P (vui[jj].lc->loc)
2947 && REG_P (node->loc)
2948 && REGNO (vui[jj].lc->loc) == REGNO (node->loc))
2949 || rtx_equal_p (vui[jj].lc->loc, node->loc))
2951 vui[jj].pos = jj + ii;
2952 break;
2955 if (jj >= dst_l) /* The location has not been found. */
2957 location_chain *new_node;
2959 /* Copy the location from SRC. */
2960 new_node = new location_chain;
2961 new_node->loc = node->loc;
2962 new_node->init = node->init;
2963 if (!node->set_src || MEM_P (node->set_src))
2964 new_node->set_src = NULL;
2965 else
2966 new_node->set_src = node->set_src;
2967 vui[n].lc = new_node;
2968 vui[n].pos_dst = src_l + dst_l;
2969 vui[n].pos = ii + src_l + dst_l;
2970 n++;
2974 if (dst_l == 2)
2976 /* Special case still very common case. For dst_l == 2
2977 all entries dst_l ... n-1 are sorted, with for i >= dst_l
2978 vui[i].pos == i + src_l + dst_l. */
2979 if (vui[0].pos > vui[1].pos)
2981 /* Order should be 1, 0, 2... */
2982 dst->var_part[k].loc_chain = vui[1].lc;
2983 vui[1].lc->next = vui[0].lc;
2984 if (n >= 3)
2986 vui[0].lc->next = vui[2].lc;
2987 vui[n - 1].lc->next = NULL;
2989 else
2990 vui[0].lc->next = NULL;
2991 ii = 3;
2993 else
2995 dst->var_part[k].loc_chain = vui[0].lc;
2996 if (n >= 3 && vui[2].pos < vui[1].pos)
2998 /* Order should be 0, 2, 1, 3... */
2999 vui[0].lc->next = vui[2].lc;
3000 vui[2].lc->next = vui[1].lc;
3001 if (n >= 4)
3003 vui[1].lc->next = vui[3].lc;
3004 vui[n - 1].lc->next = NULL;
3006 else
3007 vui[1].lc->next = NULL;
3008 ii = 4;
3010 else
3012 /* Order should be 0, 1, 2... */
3013 ii = 1;
3014 vui[n - 1].lc->next = NULL;
3017 for (; ii < n; ii++)
3018 vui[ii - 1].lc->next = vui[ii].lc;
3020 else
3022 qsort (vui, n, sizeof (struct variable_union_info),
3023 variable_union_info_cmp_pos);
3025 /* Reconnect the nodes in sorted order. */
3026 for (ii = 1; ii < n; ii++)
3027 vui[ii - 1].lc->next = vui[ii].lc;
3028 vui[n - 1].lc->next = NULL;
3029 dst->var_part[k].loc_chain = vui[0].lc;
3032 VAR_PART_OFFSET (dst, k) = VAR_PART_OFFSET (dst, j);
3034 i--;
3035 j--;
3037 else if ((i >= 0 && j >= 0
3038 && VAR_PART_OFFSET (src, i) < VAR_PART_OFFSET (dst, j))
3039 || i < 0)
3041 dst->var_part[k] = dst->var_part[j];
3042 j--;
3044 else if ((i >= 0 && j >= 0
3045 && VAR_PART_OFFSET (src, i) > VAR_PART_OFFSET (dst, j))
3046 || j < 0)
3048 location_chain **nextp;
3050 /* Copy the chain from SRC. */
3051 nextp = &dst->var_part[k].loc_chain;
3052 for (node = src->var_part[i].loc_chain; node; node = node->next)
3054 location_chain *new_lc;
3056 new_lc = new location_chain;
3057 new_lc->next = NULL;
3058 new_lc->init = node->init;
3059 if (!node->set_src || MEM_P (node->set_src))
3060 new_lc->set_src = NULL;
3061 else
3062 new_lc->set_src = node->set_src;
3063 new_lc->loc = node->loc;
3065 *nextp = new_lc;
3066 nextp = &new_lc->next;
3069 VAR_PART_OFFSET (dst, k) = VAR_PART_OFFSET (src, i);
3070 i--;
3072 dst->var_part[k].cur_loc = NULL;
3075 if (flag_var_tracking_uninit)
3076 for (i = 0; i < src->n_var_parts && i < dst->n_var_parts; i++)
3078 location_chain *node, *node2;
3079 for (node = src->var_part[i].loc_chain; node; node = node->next)
3080 for (node2 = dst->var_part[i].loc_chain; node2; node2 = node2->next)
3081 if (rtx_equal_p (node->loc, node2->loc))
3083 if (node->init > node2->init)
3084 node2->init = node->init;
3088 /* Continue traversing the hash table. */
3089 return 1;
3092 /* Compute union of dataflow sets SRC and DST and store it to DST. */
3094 static void
3095 dataflow_set_union (dataflow_set *dst, dataflow_set *src)
3097 int i;
3099 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
3100 attrs_list_union (&dst->regs[i], src->regs[i]);
3102 if (dst->vars == empty_shared_hash)
3104 shared_hash_destroy (dst->vars);
3105 dst->vars = shared_hash_copy (src->vars);
3107 else
3109 variable_iterator_type hi;
3110 variable *var;
3112 FOR_EACH_HASH_TABLE_ELEMENT (*shared_hash_htab (src->vars),
3113 var, variable, hi)
3114 variable_union (var, dst);
3118 /* Whether the value is currently being expanded. */
3119 #define VALUE_RECURSED_INTO(x) \
3120 (RTL_FLAG_CHECK2 ("VALUE_RECURSED_INTO", (x), VALUE, DEBUG_EXPR)->used)
3122 /* Whether no expansion was found, saving useless lookups.
3123 It must only be set when VALUE_CHANGED is clear. */
3124 #define NO_LOC_P(x) \
3125 (RTL_FLAG_CHECK2 ("NO_LOC_P", (x), VALUE, DEBUG_EXPR)->return_val)
3127 /* Whether cur_loc in the value needs to be (re)computed. */
3128 #define VALUE_CHANGED(x) \
3129 (RTL_FLAG_CHECK1 ("VALUE_CHANGED", (x), VALUE)->frame_related)
3130 /* Whether cur_loc in the decl needs to be (re)computed. */
3131 #define DECL_CHANGED(x) TREE_VISITED (x)
3133 /* Record (if NEWV) that DV needs to have its cur_loc recomputed. For
3134 user DECLs, this means they're in changed_variables. Values and
3135 debug exprs may be left with this flag set if no user variable
3136 requires them to be evaluated. */
3138 static inline void
3139 set_dv_changed (decl_or_value dv, bool newv)
3141 switch (dv_onepart_p (dv))
3143 case ONEPART_VALUE:
3144 if (newv)
3145 NO_LOC_P (dv_as_value (dv)) = false;
3146 VALUE_CHANGED (dv_as_value (dv)) = newv;
3147 break;
3149 case ONEPART_DEXPR:
3150 if (newv)
3151 NO_LOC_P (DECL_RTL_KNOWN_SET (dv_as_decl (dv))) = false;
3152 /* Fall through. */
3154 default:
3155 DECL_CHANGED (dv_as_decl (dv)) = newv;
3156 break;
3160 /* Return true if DV needs to have its cur_loc recomputed. */
3162 static inline bool
3163 dv_changed_p (decl_or_value dv)
3165 return (dv_is_value_p (dv)
3166 ? VALUE_CHANGED (dv_as_value (dv))
3167 : DECL_CHANGED (dv_as_decl (dv)));
3170 /* Return a location list node whose loc is rtx_equal to LOC, in the
3171 location list of a one-part variable or value VAR, or in that of
3172 any values recursively mentioned in the location lists. VARS must
3173 be in star-canonical form. */
3175 static location_chain *
3176 find_loc_in_1pdv (rtx loc, variable *var, variable_table_type *vars)
3178 location_chain *node;
3179 enum rtx_code loc_code;
3181 if (!var)
3182 return NULL;
3184 gcc_checking_assert (var->onepart);
3186 if (!var->n_var_parts)
3187 return NULL;
3189 gcc_checking_assert (loc != dv_as_opaque (var->dv));
3191 loc_code = GET_CODE (loc);
3192 for (node = var->var_part[0].loc_chain; node; node = node->next)
3194 decl_or_value dv;
3195 variable *rvar;
3197 if (GET_CODE (node->loc) != loc_code)
3199 if (GET_CODE (node->loc) != VALUE)
3200 continue;
3202 else if (loc == node->loc)
3203 return node;
3204 else if (loc_code != VALUE)
3206 if (rtx_equal_p (loc, node->loc))
3207 return node;
3208 continue;
3211 /* Since we're in star-canonical form, we don't need to visit
3212 non-canonical nodes: one-part variables and non-canonical
3213 values would only point back to the canonical node. */
3214 if (dv_is_value_p (var->dv)
3215 && !canon_value_cmp (node->loc, dv_as_value (var->dv)))
3217 /* Skip all subsequent VALUEs. */
3218 while (node->next && GET_CODE (node->next->loc) == VALUE)
3220 node = node->next;
3221 gcc_checking_assert (!canon_value_cmp (node->loc,
3222 dv_as_value (var->dv)));
3223 if (loc == node->loc)
3224 return node;
3226 continue;
3229 gcc_checking_assert (node == var->var_part[0].loc_chain);
3230 gcc_checking_assert (!node->next);
3232 dv = dv_from_value (node->loc);
3233 rvar = vars->find_with_hash (dv, dv_htab_hash (dv));
3234 return find_loc_in_1pdv (loc, rvar, vars);
3237 /* ??? Gotta look in cselib_val locations too. */
3239 return NULL;
3242 /* Hash table iteration argument passed to variable_merge. */
3243 struct dfset_merge
3245 /* The set in which the merge is to be inserted. */
3246 dataflow_set *dst;
3247 /* The set that we're iterating in. */
3248 dataflow_set *cur;
3249 /* The set that may contain the other dv we are to merge with. */
3250 dataflow_set *src;
3251 /* Number of onepart dvs in src. */
3252 int src_onepart_cnt;
3255 /* Insert LOC in *DNODE, if it's not there yet. The list must be in
3256 loc_cmp order, and it is maintained as such. */
3258 static void
3259 insert_into_intersection (location_chain **nodep, rtx loc,
3260 enum var_init_status status)
3262 location_chain *node;
3263 int r;
3265 for (node = *nodep; node; nodep = &node->next, node = *nodep)
3266 if ((r = loc_cmp (node->loc, loc)) == 0)
3268 node->init = MIN (node->init, status);
3269 return;
3271 else if (r > 0)
3272 break;
3274 node = new location_chain;
3276 node->loc = loc;
3277 node->set_src = NULL;
3278 node->init = status;
3279 node->next = *nodep;
3280 *nodep = node;
3283 /* Insert in DEST the intersection of the locations present in both
3284 S1NODE and S2VAR, directly or indirectly. S1NODE is from a
3285 variable in DSM->cur, whereas S2VAR is from DSM->src. dvar is in
3286 DSM->dst. */
3288 static void
3289 intersect_loc_chains (rtx val, location_chain **dest, struct dfset_merge *dsm,
3290 location_chain *s1node, variable *s2var)
3292 dataflow_set *s1set = dsm->cur;
3293 dataflow_set *s2set = dsm->src;
3294 location_chain *found;
3296 if (s2var)
3298 location_chain *s2node;
3300 gcc_checking_assert (s2var->onepart);
3302 if (s2var->n_var_parts)
3304 s2node = s2var->var_part[0].loc_chain;
3306 for (; s1node && s2node;
3307 s1node = s1node->next, s2node = s2node->next)
3308 if (s1node->loc != s2node->loc)
3309 break;
3310 else if (s1node->loc == val)
3311 continue;
3312 else
3313 insert_into_intersection (dest, s1node->loc,
3314 MIN (s1node->init, s2node->init));
3318 for (; s1node; s1node = s1node->next)
3320 if (s1node->loc == val)
3321 continue;
3323 if ((found = find_loc_in_1pdv (s1node->loc, s2var,
3324 shared_hash_htab (s2set->vars))))
3326 insert_into_intersection (dest, s1node->loc,
3327 MIN (s1node->init, found->init));
3328 continue;
3331 if (GET_CODE (s1node->loc) == VALUE
3332 && !VALUE_RECURSED_INTO (s1node->loc))
3334 decl_or_value dv = dv_from_value (s1node->loc);
3335 variable *svar = shared_hash_find (s1set->vars, dv);
3336 if (svar)
3338 if (svar->n_var_parts == 1)
3340 VALUE_RECURSED_INTO (s1node->loc) = true;
3341 intersect_loc_chains (val, dest, dsm,
3342 svar->var_part[0].loc_chain,
3343 s2var);
3344 VALUE_RECURSED_INTO (s1node->loc) = false;
3349 /* ??? gotta look in cselib_val locations too. */
3351 /* ??? if the location is equivalent to any location in src,
3352 searched recursively
3354 add to dst the values needed to represent the equivalence
3356 telling whether locations S is equivalent to another dv's
3357 location list:
3359 for each location D in the list
3361 if S and D satisfy rtx_equal_p, then it is present
3363 else if D is a value, recurse without cycles
3365 else if S and D have the same CODE and MODE
3367 for each operand oS and the corresponding oD
3369 if oS and oD are not equivalent, then S an D are not equivalent
3371 else if they are RTX vectors
3373 if any vector oS element is not equivalent to its respective oD,
3374 then S and D are not equivalent
3382 /* Return -1 if X should be before Y in a location list for a 1-part
3383 variable, 1 if Y should be before X, and 0 if they're equivalent
3384 and should not appear in the list. */
3386 static int
3387 loc_cmp (rtx x, rtx y)
3389 int i, j, r;
3390 RTX_CODE code = GET_CODE (x);
3391 const char *fmt;
3393 if (x == y)
3394 return 0;
3396 if (REG_P (x))
3398 if (!REG_P (y))
3399 return -1;
3400 gcc_assert (GET_MODE (x) == GET_MODE (y));
3401 if (REGNO (x) == REGNO (y))
3402 return 0;
3403 else if (REGNO (x) < REGNO (y))
3404 return -1;
3405 else
3406 return 1;
3409 if (REG_P (y))
3410 return 1;
3412 if (MEM_P (x))
3414 if (!MEM_P (y))
3415 return -1;
3416 gcc_assert (GET_MODE (x) == GET_MODE (y));
3417 return loc_cmp (XEXP (x, 0), XEXP (y, 0));
3420 if (MEM_P (y))
3421 return 1;
3423 if (GET_CODE (x) == VALUE)
3425 if (GET_CODE (y) != VALUE)
3426 return -1;
3427 /* Don't assert the modes are the same, that is true only
3428 when not recursing. (subreg:QI (value:SI 1:1) 0)
3429 and (subreg:QI (value:DI 2:2) 0) can be compared,
3430 even when the modes are different. */
3431 if (canon_value_cmp (x, y))
3432 return -1;
3433 else
3434 return 1;
3437 if (GET_CODE (y) == VALUE)
3438 return 1;
3440 /* Entry value is the least preferable kind of expression. */
3441 if (GET_CODE (x) == ENTRY_VALUE)
3443 if (GET_CODE (y) != ENTRY_VALUE)
3444 return 1;
3445 gcc_assert (GET_MODE (x) == GET_MODE (y));
3446 return loc_cmp (ENTRY_VALUE_EXP (x), ENTRY_VALUE_EXP (y));
3449 if (GET_CODE (y) == ENTRY_VALUE)
3450 return -1;
3452 if (GET_CODE (x) == GET_CODE (y))
3453 /* Compare operands below. */;
3454 else if (GET_CODE (x) < GET_CODE (y))
3455 return -1;
3456 else
3457 return 1;
3459 gcc_assert (GET_MODE (x) == GET_MODE (y));
3461 if (GET_CODE (x) == DEBUG_EXPR)
3463 if (DEBUG_TEMP_UID (DEBUG_EXPR_TREE_DECL (x))
3464 < DEBUG_TEMP_UID (DEBUG_EXPR_TREE_DECL (y)))
3465 return -1;
3466 gcc_checking_assert (DEBUG_TEMP_UID (DEBUG_EXPR_TREE_DECL (x))
3467 > DEBUG_TEMP_UID (DEBUG_EXPR_TREE_DECL (y)));
3468 return 1;
3471 fmt = GET_RTX_FORMAT (code);
3472 for (i = 0; i < GET_RTX_LENGTH (code); i++)
3473 switch (fmt[i])
3475 case 'w':
3476 if (XWINT (x, i) == XWINT (y, i))
3477 break;
3478 else if (XWINT (x, i) < XWINT (y, i))
3479 return -1;
3480 else
3481 return 1;
3483 case 'n':
3484 case 'i':
3485 if (XINT (x, i) == XINT (y, i))
3486 break;
3487 else if (XINT (x, i) < XINT (y, i))
3488 return -1;
3489 else
3490 return 1;
3492 case 'V':
3493 case 'E':
3494 /* Compare the vector length first. */
3495 if (XVECLEN (x, i) == XVECLEN (y, i))
3496 /* Compare the vectors elements. */;
3497 else if (XVECLEN (x, i) < XVECLEN (y, i))
3498 return -1;
3499 else
3500 return 1;
3502 for (j = 0; j < XVECLEN (x, i); j++)
3503 if ((r = loc_cmp (XVECEXP (x, i, j),
3504 XVECEXP (y, i, j))))
3505 return r;
3506 break;
3508 case 'e':
3509 if ((r = loc_cmp (XEXP (x, i), XEXP (y, i))))
3510 return r;
3511 break;
3513 case 'S':
3514 case 's':
3515 if (XSTR (x, i) == XSTR (y, i))
3516 break;
3517 if (!XSTR (x, i))
3518 return -1;
3519 if (!XSTR (y, i))
3520 return 1;
3521 if ((r = strcmp (XSTR (x, i), XSTR (y, i))) == 0)
3522 break;
3523 else if (r < 0)
3524 return -1;
3525 else
3526 return 1;
3528 case 'u':
3529 /* These are just backpointers, so they don't matter. */
3530 break;
3532 case '0':
3533 case 't':
3534 break;
3536 /* It is believed that rtx's at this level will never
3537 contain anything but integers and other rtx's,
3538 except for within LABEL_REFs and SYMBOL_REFs. */
3539 default:
3540 gcc_unreachable ();
3542 if (CONST_WIDE_INT_P (x))
3544 /* Compare the vector length first. */
3545 if (CONST_WIDE_INT_NUNITS (x) >= CONST_WIDE_INT_NUNITS (y))
3546 return 1;
3547 else if (CONST_WIDE_INT_NUNITS (x) < CONST_WIDE_INT_NUNITS (y))
3548 return -1;
3550 /* Compare the vectors elements. */;
3551 for (j = CONST_WIDE_INT_NUNITS (x) - 1; j >= 0 ; j--)
3553 if (CONST_WIDE_INT_ELT (x, j) < CONST_WIDE_INT_ELT (y, j))
3554 return -1;
3555 if (CONST_WIDE_INT_ELT (x, j) > CONST_WIDE_INT_ELT (y, j))
3556 return 1;
3560 return 0;
3563 /* Check the order of entries in one-part variables. */
3566 canonicalize_loc_order_check (variable **slot,
3567 dataflow_set *data ATTRIBUTE_UNUSED)
3569 variable *var = *slot;
3570 location_chain *node, *next;
3572 #ifdef ENABLE_RTL_CHECKING
3573 int i;
3574 for (i = 0; i < var->n_var_parts; i++)
3575 gcc_assert (var->var_part[0].cur_loc == NULL);
3576 gcc_assert (!var->in_changed_variables);
3577 #endif
3579 if (!var->onepart)
3580 return 1;
3582 gcc_assert (var->n_var_parts == 1);
3583 node = var->var_part[0].loc_chain;
3584 gcc_assert (node);
3586 while ((next = node->next))
3588 gcc_assert (loc_cmp (node->loc, next->loc) < 0);
3589 node = next;
3592 return 1;
3595 /* Mark with VALUE_RECURSED_INTO values that have neighbors that are
3596 more likely to be chosen as canonical for an equivalence set.
3597 Ensure less likely values can reach more likely neighbors, making
3598 the connections bidirectional. */
3601 canonicalize_values_mark (variable **slot, dataflow_set *set)
3603 variable *var = *slot;
3604 decl_or_value dv = var->dv;
3605 rtx val;
3606 location_chain *node;
3608 if (!dv_is_value_p (dv))
3609 return 1;
3611 gcc_checking_assert (var->n_var_parts == 1);
3613 val = dv_as_value (dv);
3615 for (node = var->var_part[0].loc_chain; node; node = node->next)
3616 if (GET_CODE (node->loc) == VALUE)
3618 if (canon_value_cmp (node->loc, val))
3619 VALUE_RECURSED_INTO (val) = true;
3620 else
3622 decl_or_value odv = dv_from_value (node->loc);
3623 variable **oslot;
3624 oslot = shared_hash_find_slot_noinsert (set->vars, odv);
3626 set_slot_part (set, val, oslot, odv, 0,
3627 node->init, NULL_RTX);
3629 VALUE_RECURSED_INTO (node->loc) = true;
3633 return 1;
3636 /* Remove redundant entries from equivalence lists in onepart
3637 variables, canonicalizing equivalence sets into star shapes. */
3640 canonicalize_values_star (variable **slot, dataflow_set *set)
3642 variable *var = *slot;
3643 decl_or_value dv = var->dv;
3644 location_chain *node;
3645 decl_or_value cdv;
3646 rtx val, cval;
3647 variable **cslot;
3648 bool has_value;
3649 bool has_marks;
3651 if (!var->onepart)
3652 return 1;
3654 gcc_checking_assert (var->n_var_parts == 1);
3656 if (dv_is_value_p (dv))
3658 cval = dv_as_value (dv);
3659 if (!VALUE_RECURSED_INTO (cval))
3660 return 1;
3661 VALUE_RECURSED_INTO (cval) = false;
3663 else
3664 cval = NULL_RTX;
3666 restart:
3667 val = cval;
3668 has_value = false;
3669 has_marks = false;
3671 gcc_assert (var->n_var_parts == 1);
3673 for (node = var->var_part[0].loc_chain; node; node = node->next)
3674 if (GET_CODE (node->loc) == VALUE)
3676 has_value = true;
3677 if (VALUE_RECURSED_INTO (node->loc))
3678 has_marks = true;
3679 if (canon_value_cmp (node->loc, cval))
3680 cval = node->loc;
3683 if (!has_value)
3684 return 1;
3686 if (cval == val)
3688 if (!has_marks || dv_is_decl_p (dv))
3689 return 1;
3691 /* Keep it marked so that we revisit it, either after visiting a
3692 child node, or after visiting a new parent that might be
3693 found out. */
3694 VALUE_RECURSED_INTO (val) = true;
3696 for (node = var->var_part[0].loc_chain; node; node = node->next)
3697 if (GET_CODE (node->loc) == VALUE
3698 && VALUE_RECURSED_INTO (node->loc))
3700 cval = node->loc;
3701 restart_with_cval:
3702 VALUE_RECURSED_INTO (cval) = false;
3703 dv = dv_from_value (cval);
3704 slot = shared_hash_find_slot_noinsert (set->vars, dv);
3705 if (!slot)
3707 gcc_assert (dv_is_decl_p (var->dv));
3708 /* The canonical value was reset and dropped.
3709 Remove it. */
3710 clobber_variable_part (set, NULL, var->dv, 0, NULL);
3711 return 1;
3713 var = *slot;
3714 gcc_assert (dv_is_value_p (var->dv));
3715 if (var->n_var_parts == 0)
3716 return 1;
3717 gcc_assert (var->n_var_parts == 1);
3718 goto restart;
3721 VALUE_RECURSED_INTO (val) = false;
3723 return 1;
3726 /* Push values to the canonical one. */
3727 cdv = dv_from_value (cval);
3728 cslot = shared_hash_find_slot_noinsert (set->vars, cdv);
3730 for (node = var->var_part[0].loc_chain; node; node = node->next)
3731 if (node->loc != cval)
3733 cslot = set_slot_part (set, node->loc, cslot, cdv, 0,
3734 node->init, NULL_RTX);
3735 if (GET_CODE (node->loc) == VALUE)
3737 decl_or_value ndv = dv_from_value (node->loc);
3739 set_variable_part (set, cval, ndv, 0, node->init, NULL_RTX,
3740 NO_INSERT);
3742 if (canon_value_cmp (node->loc, val))
3744 /* If it could have been a local minimum, it's not any more,
3745 since it's now neighbor to cval, so it may have to push
3746 to it. Conversely, if it wouldn't have prevailed over
3747 val, then whatever mark it has is fine: if it was to
3748 push, it will now push to a more canonical node, but if
3749 it wasn't, then it has already pushed any values it might
3750 have to. */
3751 VALUE_RECURSED_INTO (node->loc) = true;
3752 /* Make sure we visit node->loc by ensuring we cval is
3753 visited too. */
3754 VALUE_RECURSED_INTO (cval) = true;
3756 else if (!VALUE_RECURSED_INTO (node->loc))
3757 /* If we have no need to "recurse" into this node, it's
3758 already "canonicalized", so drop the link to the old
3759 parent. */
3760 clobber_variable_part (set, cval, ndv, 0, NULL);
3762 else if (GET_CODE (node->loc) == REG)
3764 attrs *list = set->regs[REGNO (node->loc)], **listp;
3766 /* Change an existing attribute referring to dv so that it
3767 refers to cdv, removing any duplicate this might
3768 introduce, and checking that no previous duplicates
3769 existed, all in a single pass. */
3771 while (list)
3773 if (list->offset == 0
3774 && (dv_as_opaque (list->dv) == dv_as_opaque (dv)
3775 || dv_as_opaque (list->dv) == dv_as_opaque (cdv)))
3776 break;
3778 list = list->next;
3781 gcc_assert (list);
3782 if (dv_as_opaque (list->dv) == dv_as_opaque (dv))
3784 list->dv = cdv;
3785 for (listp = &list->next; (list = *listp); listp = &list->next)
3787 if (list->offset)
3788 continue;
3790 if (dv_as_opaque (list->dv) == dv_as_opaque (cdv))
3792 *listp = list->next;
3793 delete list;
3794 list = *listp;
3795 break;
3798 gcc_assert (dv_as_opaque (list->dv) != dv_as_opaque (dv));
3801 else if (dv_as_opaque (list->dv) == dv_as_opaque (cdv))
3803 for (listp = &list->next; (list = *listp); listp = &list->next)
3805 if (list->offset)
3806 continue;
3808 if (dv_as_opaque (list->dv) == dv_as_opaque (dv))
3810 *listp = list->next;
3811 delete list;
3812 list = *listp;
3813 break;
3816 gcc_assert (dv_as_opaque (list->dv) != dv_as_opaque (cdv));
3819 else
3820 gcc_unreachable ();
3822 if (flag_checking)
3823 while (list)
3825 if (list->offset == 0
3826 && (dv_as_opaque (list->dv) == dv_as_opaque (dv)
3827 || dv_as_opaque (list->dv) == dv_as_opaque (cdv)))
3828 gcc_unreachable ();
3830 list = list->next;
3835 if (val)
3836 set_slot_part (set, val, cslot, cdv, 0,
3837 VAR_INIT_STATUS_INITIALIZED, NULL_RTX);
3839 slot = clobber_slot_part (set, cval, slot, 0, NULL);
3841 /* Variable may have been unshared. */
3842 var = *slot;
3843 gcc_checking_assert (var->n_var_parts && var->var_part[0].loc_chain->loc == cval
3844 && var->var_part[0].loc_chain->next == NULL);
3846 if (VALUE_RECURSED_INTO (cval))
3847 goto restart_with_cval;
3849 return 1;
3852 /* Bind one-part variables to the canonical value in an equivalence
3853 set. Not doing this causes dataflow convergence failure in rare
3854 circumstances, see PR42873. Unfortunately we can't do this
3855 efficiently as part of canonicalize_values_star, since we may not
3856 have determined or even seen the canonical value of a set when we
3857 get to a variable that references another member of the set. */
3860 canonicalize_vars_star (variable **slot, dataflow_set *set)
3862 variable *var = *slot;
3863 decl_or_value dv = var->dv;
3864 location_chain *node;
3865 rtx cval;
3866 decl_or_value cdv;
3867 variable **cslot;
3868 variable *cvar;
3869 location_chain *cnode;
3871 if (!var->onepart || var->onepart == ONEPART_VALUE)
3872 return 1;
3874 gcc_assert (var->n_var_parts == 1);
3876 node = var->var_part[0].loc_chain;
3878 if (GET_CODE (node->loc) != VALUE)
3879 return 1;
3881 gcc_assert (!node->next);
3882 cval = node->loc;
3884 /* Push values to the canonical one. */
3885 cdv = dv_from_value (cval);
3886 cslot = shared_hash_find_slot_noinsert (set->vars, cdv);
3887 if (!cslot)
3888 return 1;
3889 cvar = *cslot;
3890 gcc_assert (cvar->n_var_parts == 1);
3892 cnode = cvar->var_part[0].loc_chain;
3894 /* CVAL is canonical if its value list contains non-VALUEs or VALUEs
3895 that are not “more canonical” than it. */
3896 if (GET_CODE (cnode->loc) != VALUE
3897 || !canon_value_cmp (cnode->loc, cval))
3898 return 1;
3900 /* CVAL was found to be non-canonical. Change the variable to point
3901 to the canonical VALUE. */
3902 gcc_assert (!cnode->next);
3903 cval = cnode->loc;
3905 slot = set_slot_part (set, cval, slot, dv, 0,
3906 node->init, node->set_src);
3907 clobber_slot_part (set, cval, slot, 0, node->set_src);
3909 return 1;
3912 /* Combine variable or value in *S1SLOT (in DSM->cur) with the
3913 corresponding entry in DSM->src. Multi-part variables are combined
3914 with variable_union, whereas onepart dvs are combined with
3915 intersection. */
3917 static int
3918 variable_merge_over_cur (variable *s1var, struct dfset_merge *dsm)
3920 dataflow_set *dst = dsm->dst;
3921 variable **dstslot;
3922 variable *s2var, *dvar = NULL;
3923 decl_or_value dv = s1var->dv;
3924 onepart_enum onepart = s1var->onepart;
3925 rtx val;
3926 hashval_t dvhash;
3927 location_chain *node, **nodep;
3929 /* If the incoming onepart variable has an empty location list, then
3930 the intersection will be just as empty. For other variables,
3931 it's always union. */
3932 gcc_checking_assert (s1var->n_var_parts
3933 && s1var->var_part[0].loc_chain);
3935 if (!onepart)
3936 return variable_union (s1var, dst);
3938 gcc_checking_assert (s1var->n_var_parts == 1);
3940 dvhash = dv_htab_hash (dv);
3941 if (dv_is_value_p (dv))
3942 val = dv_as_value (dv);
3943 else
3944 val = NULL;
3946 s2var = shared_hash_find_1 (dsm->src->vars, dv, dvhash);
3947 if (!s2var)
3949 dst_can_be_shared = false;
3950 return 1;
3953 dsm->src_onepart_cnt--;
3954 gcc_assert (s2var->var_part[0].loc_chain
3955 && s2var->onepart == onepart
3956 && s2var->n_var_parts == 1);
3958 dstslot = shared_hash_find_slot_noinsert_1 (dst->vars, dv, dvhash);
3959 if (dstslot)
3961 dvar = *dstslot;
3962 gcc_assert (dvar->refcount == 1
3963 && dvar->onepart == onepart
3964 && dvar->n_var_parts == 1);
3965 nodep = &dvar->var_part[0].loc_chain;
3967 else
3969 nodep = &node;
3970 node = NULL;
3973 if (!dstslot && !onepart_variable_different_p (s1var, s2var))
3975 dstslot = shared_hash_find_slot_unshare_1 (&dst->vars, dv,
3976 dvhash, INSERT);
3977 *dstslot = dvar = s2var;
3978 dvar->refcount++;
3980 else
3982 dst_can_be_shared = false;
3984 intersect_loc_chains (val, nodep, dsm,
3985 s1var->var_part[0].loc_chain, s2var);
3987 if (!dstslot)
3989 if (node)
3991 dvar = onepart_pool_allocate (onepart);
3992 dvar->dv = dv;
3993 dvar->refcount = 1;
3994 dvar->n_var_parts = 1;
3995 dvar->onepart = onepart;
3996 dvar->in_changed_variables = false;
3997 dvar->var_part[0].loc_chain = node;
3998 dvar->var_part[0].cur_loc = NULL;
3999 if (onepart)
4000 VAR_LOC_1PAUX (dvar) = NULL;
4001 else
4002 VAR_PART_OFFSET (dvar, 0) = 0;
4004 dstslot
4005 = shared_hash_find_slot_unshare_1 (&dst->vars, dv, dvhash,
4006 INSERT);
4007 gcc_assert (!*dstslot);
4008 *dstslot = dvar;
4010 else
4011 return 1;
4015 nodep = &dvar->var_part[0].loc_chain;
4016 while ((node = *nodep))
4018 location_chain **nextp = &node->next;
4020 if (GET_CODE (node->loc) == REG)
4022 attrs *list;
4024 for (list = dst->regs[REGNO (node->loc)]; list; list = list->next)
4025 if (GET_MODE (node->loc) == GET_MODE (list->loc)
4026 && dv_is_value_p (list->dv))
4027 break;
4029 if (!list)
4030 attrs_list_insert (&dst->regs[REGNO (node->loc)],
4031 dv, 0, node->loc);
4032 /* If this value became canonical for another value that had
4033 this register, we want to leave it alone. */
4034 else if (dv_as_value (list->dv) != val)
4036 dstslot = set_slot_part (dst, dv_as_value (list->dv),
4037 dstslot, dv, 0,
4038 node->init, NULL_RTX);
4039 dstslot = delete_slot_part (dst, node->loc, dstslot, 0);
4041 /* Since nextp points into the removed node, we can't
4042 use it. The pointer to the next node moved to nodep.
4043 However, if the variable we're walking is unshared
4044 during our walk, we'll keep walking the location list
4045 of the previously-shared variable, in which case the
4046 node won't have been removed, and we'll want to skip
4047 it. That's why we test *nodep here. */
4048 if (*nodep != node)
4049 nextp = nodep;
4052 else
4053 /* Canonicalization puts registers first, so we don't have to
4054 walk it all. */
4055 break;
4056 nodep = nextp;
4059 if (dvar != *dstslot)
4060 dvar = *dstslot;
4061 nodep = &dvar->var_part[0].loc_chain;
4063 if (val)
4065 /* Mark all referenced nodes for canonicalization, and make sure
4066 we have mutual equivalence links. */
4067 VALUE_RECURSED_INTO (val) = true;
4068 for (node = *nodep; node; node = node->next)
4069 if (GET_CODE (node->loc) == VALUE)
4071 VALUE_RECURSED_INTO (node->loc) = true;
4072 set_variable_part (dst, val, dv_from_value (node->loc), 0,
4073 node->init, NULL, INSERT);
4076 dstslot = shared_hash_find_slot_noinsert_1 (dst->vars, dv, dvhash);
4077 gcc_assert (*dstslot == dvar);
4078 canonicalize_values_star (dstslot, dst);
4079 gcc_checking_assert (dstslot
4080 == shared_hash_find_slot_noinsert_1 (dst->vars,
4081 dv, dvhash));
4082 dvar = *dstslot;
4084 else
4086 bool has_value = false, has_other = false;
4088 /* If we have one value and anything else, we're going to
4089 canonicalize this, so make sure all values have an entry in
4090 the table and are marked for canonicalization. */
4091 for (node = *nodep; node; node = node->next)
4093 if (GET_CODE (node->loc) == VALUE)
4095 /* If this was marked during register canonicalization,
4096 we know we have to canonicalize values. */
4097 if (has_value)
4098 has_other = true;
4099 has_value = true;
4100 if (has_other)
4101 break;
4103 else
4105 has_other = true;
4106 if (has_value)
4107 break;
4111 if (has_value && has_other)
4113 for (node = *nodep; node; node = node->next)
4115 if (GET_CODE (node->loc) == VALUE)
4117 decl_or_value dv = dv_from_value (node->loc);
4118 variable **slot = NULL;
4120 if (shared_hash_shared (dst->vars))
4121 slot = shared_hash_find_slot_noinsert (dst->vars, dv);
4122 if (!slot)
4123 slot = shared_hash_find_slot_unshare (&dst->vars, dv,
4124 INSERT);
4125 if (!*slot)
4127 variable *var = onepart_pool_allocate (ONEPART_VALUE);
4128 var->dv = dv;
4129 var->refcount = 1;
4130 var->n_var_parts = 1;
4131 var->onepart = ONEPART_VALUE;
4132 var->in_changed_variables = false;
4133 var->var_part[0].loc_chain = NULL;
4134 var->var_part[0].cur_loc = NULL;
4135 VAR_LOC_1PAUX (var) = NULL;
4136 *slot = var;
4139 VALUE_RECURSED_INTO (node->loc) = true;
4143 dstslot = shared_hash_find_slot_noinsert_1 (dst->vars, dv, dvhash);
4144 gcc_assert (*dstslot == dvar);
4145 canonicalize_values_star (dstslot, dst);
4146 gcc_checking_assert (dstslot
4147 == shared_hash_find_slot_noinsert_1 (dst->vars,
4148 dv, dvhash));
4149 dvar = *dstslot;
4153 if (!onepart_variable_different_p (dvar, s2var))
4155 variable_htab_free (dvar);
4156 *dstslot = dvar = s2var;
4157 dvar->refcount++;
4159 else if (s2var != s1var && !onepart_variable_different_p (dvar, s1var))
4161 variable_htab_free (dvar);
4162 *dstslot = dvar = s1var;
4163 dvar->refcount++;
4164 dst_can_be_shared = false;
4166 else
4167 dst_can_be_shared = false;
4169 return 1;
4172 /* Copy s2slot (in DSM->src) to DSM->dst if the variable is a
4173 multi-part variable. Unions of multi-part variables and
4174 intersections of one-part ones will be handled in
4175 variable_merge_over_cur(). */
4177 static int
4178 variable_merge_over_src (variable *s2var, struct dfset_merge *dsm)
4180 dataflow_set *dst = dsm->dst;
4181 decl_or_value dv = s2var->dv;
4183 if (!s2var->onepart)
4185 variable **dstp = shared_hash_find_slot (dst->vars, dv);
4186 *dstp = s2var;
4187 s2var->refcount++;
4188 return 1;
4191 dsm->src_onepart_cnt++;
4192 return 1;
4195 /* Combine dataflow set information from SRC2 into DST, using PDST
4196 to carry over information across passes. */
4198 static void
4199 dataflow_set_merge (dataflow_set *dst, dataflow_set *src2)
4201 dataflow_set cur = *dst;
4202 dataflow_set *src1 = &cur;
4203 struct dfset_merge dsm;
4204 int i;
4205 size_t src1_elems, src2_elems;
4206 variable_iterator_type hi;
4207 variable *var;
4209 src1_elems = shared_hash_htab (src1->vars)->elements ();
4210 src2_elems = shared_hash_htab (src2->vars)->elements ();
4211 dataflow_set_init (dst);
4212 dst->stack_adjust = cur.stack_adjust;
4213 shared_hash_destroy (dst->vars);
4214 dst->vars = new shared_hash;
4215 dst->vars->refcount = 1;
4216 dst->vars->htab = new variable_table_type (MAX (src1_elems, src2_elems));
4218 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
4219 attrs_list_mpdv_union (&dst->regs[i], src1->regs[i], src2->regs[i]);
4221 dsm.dst = dst;
4222 dsm.src = src2;
4223 dsm.cur = src1;
4224 dsm.src_onepart_cnt = 0;
4226 FOR_EACH_HASH_TABLE_ELEMENT (*shared_hash_htab (dsm.src->vars),
4227 var, variable, hi)
4228 variable_merge_over_src (var, &dsm);
4229 FOR_EACH_HASH_TABLE_ELEMENT (*shared_hash_htab (dsm.cur->vars),
4230 var, variable, hi)
4231 variable_merge_over_cur (var, &dsm);
4233 if (dsm.src_onepart_cnt)
4234 dst_can_be_shared = false;
4236 dataflow_set_destroy (src1);
4239 /* Mark register equivalences. */
4241 static void
4242 dataflow_set_equiv_regs (dataflow_set *set)
4244 int i;
4245 attrs *list, **listp;
4247 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
4249 rtx canon[NUM_MACHINE_MODES];
4251 /* If the list is empty or one entry, no need to canonicalize
4252 anything. */
4253 if (set->regs[i] == NULL || set->regs[i]->next == NULL)
4254 continue;
4256 memset (canon, 0, sizeof (canon));
4258 for (list = set->regs[i]; list; list = list->next)
4259 if (list->offset == 0 && dv_is_value_p (list->dv))
4261 rtx val = dv_as_value (list->dv);
4262 rtx *cvalp = &canon[(int)GET_MODE (val)];
4263 rtx cval = *cvalp;
4265 if (canon_value_cmp (val, cval))
4266 *cvalp = val;
4269 for (list = set->regs[i]; list; list = list->next)
4270 if (list->offset == 0 && dv_onepart_p (list->dv))
4272 rtx cval = canon[(int)GET_MODE (list->loc)];
4274 if (!cval)
4275 continue;
4277 if (dv_is_value_p (list->dv))
4279 rtx val = dv_as_value (list->dv);
4281 if (val == cval)
4282 continue;
4284 VALUE_RECURSED_INTO (val) = true;
4285 set_variable_part (set, val, dv_from_value (cval), 0,
4286 VAR_INIT_STATUS_INITIALIZED,
4287 NULL, NO_INSERT);
4290 VALUE_RECURSED_INTO (cval) = true;
4291 set_variable_part (set, cval, list->dv, 0,
4292 VAR_INIT_STATUS_INITIALIZED, NULL, NO_INSERT);
4295 for (listp = &set->regs[i]; (list = *listp);
4296 listp = list ? &list->next : listp)
4297 if (list->offset == 0 && dv_onepart_p (list->dv))
4299 rtx cval = canon[(int)GET_MODE (list->loc)];
4300 variable **slot;
4302 if (!cval)
4303 continue;
4305 if (dv_is_value_p (list->dv))
4307 rtx val = dv_as_value (list->dv);
4308 if (!VALUE_RECURSED_INTO (val))
4309 continue;
4312 slot = shared_hash_find_slot_noinsert (set->vars, list->dv);
4313 canonicalize_values_star (slot, set);
4314 if (*listp != list)
4315 list = NULL;
4320 /* Remove any redundant values in the location list of VAR, which must
4321 be unshared and 1-part. */
4323 static void
4324 remove_duplicate_values (variable *var)
4326 location_chain *node, **nodep;
4328 gcc_assert (var->onepart);
4329 gcc_assert (var->n_var_parts == 1);
4330 gcc_assert (var->refcount == 1);
4332 for (nodep = &var->var_part[0].loc_chain; (node = *nodep); )
4334 if (GET_CODE (node->loc) == VALUE)
4336 if (VALUE_RECURSED_INTO (node->loc))
4338 /* Remove duplicate value node. */
4339 *nodep = node->next;
4340 delete node;
4341 continue;
4343 else
4344 VALUE_RECURSED_INTO (node->loc) = true;
4346 nodep = &node->next;
4349 for (node = var->var_part[0].loc_chain; node; node = node->next)
4350 if (GET_CODE (node->loc) == VALUE)
4352 gcc_assert (VALUE_RECURSED_INTO (node->loc));
4353 VALUE_RECURSED_INTO (node->loc) = false;
4358 /* Hash table iteration argument passed to variable_post_merge. */
4359 struct dfset_post_merge
4361 /* The new input set for the current block. */
4362 dataflow_set *set;
4363 /* Pointer to the permanent input set for the current block, or
4364 NULL. */
4365 dataflow_set **permp;
4368 /* Create values for incoming expressions associated with one-part
4369 variables that don't have value numbers for them. */
4372 variable_post_merge_new_vals (variable **slot, dfset_post_merge *dfpm)
4374 dataflow_set *set = dfpm->set;
4375 variable *var = *slot;
4376 location_chain *node;
4378 if (!var->onepart || !var->n_var_parts)
4379 return 1;
4381 gcc_assert (var->n_var_parts == 1);
4383 if (dv_is_decl_p (var->dv))
4385 bool check_dupes = false;
4387 restart:
4388 for (node = var->var_part[0].loc_chain; node; node = node->next)
4390 if (GET_CODE (node->loc) == VALUE)
4391 gcc_assert (!VALUE_RECURSED_INTO (node->loc));
4392 else if (GET_CODE (node->loc) == REG)
4394 attrs *att, **attp, **curp = NULL;
4396 if (var->refcount != 1)
4398 slot = unshare_variable (set, slot, var,
4399 VAR_INIT_STATUS_INITIALIZED);
4400 var = *slot;
4401 goto restart;
4404 for (attp = &set->regs[REGNO (node->loc)]; (att = *attp);
4405 attp = &att->next)
4406 if (att->offset == 0
4407 && GET_MODE (att->loc) == GET_MODE (node->loc))
4409 if (dv_is_value_p (att->dv))
4411 rtx cval = dv_as_value (att->dv);
4412 node->loc = cval;
4413 check_dupes = true;
4414 break;
4416 else if (dv_as_opaque (att->dv) == dv_as_opaque (var->dv))
4417 curp = attp;
4420 if (!curp)
4422 curp = attp;
4423 while (*curp)
4424 if ((*curp)->offset == 0
4425 && GET_MODE ((*curp)->loc) == GET_MODE (node->loc)
4426 && dv_as_opaque ((*curp)->dv) == dv_as_opaque (var->dv))
4427 break;
4428 else
4429 curp = &(*curp)->next;
4430 gcc_assert (*curp);
4433 if (!att)
4435 decl_or_value cdv;
4436 rtx cval;
4438 if (!*dfpm->permp)
4440 *dfpm->permp = XNEW (dataflow_set);
4441 dataflow_set_init (*dfpm->permp);
4444 for (att = (*dfpm->permp)->regs[REGNO (node->loc)];
4445 att; att = att->next)
4446 if (GET_MODE (att->loc) == GET_MODE (node->loc))
4448 gcc_assert (att->offset == 0
4449 && dv_is_value_p (att->dv));
4450 val_reset (set, att->dv);
4451 break;
4454 if (att)
4456 cdv = att->dv;
4457 cval = dv_as_value (cdv);
4459 else
4461 /* Create a unique value to hold this register,
4462 that ought to be found and reused in
4463 subsequent rounds. */
4464 cselib_val *v;
4465 gcc_assert (!cselib_lookup (node->loc,
4466 GET_MODE (node->loc), 0,
4467 VOIDmode));
4468 v = cselib_lookup (node->loc, GET_MODE (node->loc), 1,
4469 VOIDmode);
4470 cselib_preserve_value (v);
4471 cselib_invalidate_rtx (node->loc);
4472 cval = v->val_rtx;
4473 cdv = dv_from_value (cval);
4474 if (dump_file)
4475 fprintf (dump_file,
4476 "Created new value %u:%u for reg %i\n",
4477 v->uid, v->hash, REGNO (node->loc));
4480 var_reg_decl_set (*dfpm->permp, node->loc,
4481 VAR_INIT_STATUS_INITIALIZED,
4482 cdv, 0, NULL, INSERT);
4484 node->loc = cval;
4485 check_dupes = true;
4488 /* Remove attribute referring to the decl, which now
4489 uses the value for the register, already existing or
4490 to be added when we bring perm in. */
4491 att = *curp;
4492 *curp = att->next;
4493 delete att;
4497 if (check_dupes)
4498 remove_duplicate_values (var);
4501 return 1;
4504 /* Reset values in the permanent set that are not associated with the
4505 chosen expression. */
4508 variable_post_merge_perm_vals (variable **pslot, dfset_post_merge *dfpm)
4510 dataflow_set *set = dfpm->set;
4511 variable *pvar = *pslot, *var;
4512 location_chain *pnode;
4513 decl_or_value dv;
4514 attrs *att;
4516 gcc_assert (dv_is_value_p (pvar->dv)
4517 && pvar->n_var_parts == 1);
4518 pnode = pvar->var_part[0].loc_chain;
4519 gcc_assert (pnode
4520 && !pnode->next
4521 && REG_P (pnode->loc));
4523 dv = pvar->dv;
4525 var = shared_hash_find (set->vars, dv);
4526 if (var)
4528 /* Although variable_post_merge_new_vals may have made decls
4529 non-star-canonical, values that pre-existed in canonical form
4530 remain canonical, and newly-created values reference a single
4531 REG, so they are canonical as well. Since VAR has the
4532 location list for a VALUE, using find_loc_in_1pdv for it is
4533 fine, since VALUEs don't map back to DECLs. */
4534 if (find_loc_in_1pdv (pnode->loc, var, shared_hash_htab (set->vars)))
4535 return 1;
4536 val_reset (set, dv);
4539 for (att = set->regs[REGNO (pnode->loc)]; att; att = att->next)
4540 if (att->offset == 0
4541 && GET_MODE (att->loc) == GET_MODE (pnode->loc)
4542 && dv_is_value_p (att->dv))
4543 break;
4545 /* If there is a value associated with this register already, create
4546 an equivalence. */
4547 if (att && dv_as_value (att->dv) != dv_as_value (dv))
4549 rtx cval = dv_as_value (att->dv);
4550 set_variable_part (set, cval, dv, 0, pnode->init, NULL, INSERT);
4551 set_variable_part (set, dv_as_value (dv), att->dv, 0, pnode->init,
4552 NULL, INSERT);
4554 else if (!att)
4556 attrs_list_insert (&set->regs[REGNO (pnode->loc)],
4557 dv, 0, pnode->loc);
4558 variable_union (pvar, set);
4561 return 1;
4564 /* Just checking stuff and registering register attributes for
4565 now. */
4567 static void
4568 dataflow_post_merge_adjust (dataflow_set *set, dataflow_set **permp)
4570 struct dfset_post_merge dfpm;
4572 dfpm.set = set;
4573 dfpm.permp = permp;
4575 shared_hash_htab (set->vars)
4576 ->traverse <dfset_post_merge*, variable_post_merge_new_vals> (&dfpm);
4577 if (*permp)
4578 shared_hash_htab ((*permp)->vars)
4579 ->traverse <dfset_post_merge*, variable_post_merge_perm_vals> (&dfpm);
4580 shared_hash_htab (set->vars)
4581 ->traverse <dataflow_set *, canonicalize_values_star> (set);
4582 shared_hash_htab (set->vars)
4583 ->traverse <dataflow_set *, canonicalize_vars_star> (set);
4586 /* Return a node whose loc is a MEM that refers to EXPR in the
4587 location list of a one-part variable or value VAR, or in that of
4588 any values recursively mentioned in the location lists. */
4590 static location_chain *
4591 find_mem_expr_in_1pdv (tree expr, rtx val, variable_table_type *vars)
4593 location_chain *node;
4594 decl_or_value dv;
4595 variable *var;
4596 location_chain *where = NULL;
4598 if (!val)
4599 return NULL;
4601 gcc_assert (GET_CODE (val) == VALUE
4602 && !VALUE_RECURSED_INTO (val));
4604 dv = dv_from_value (val);
4605 var = vars->find_with_hash (dv, dv_htab_hash (dv));
4607 if (!var)
4608 return NULL;
4610 gcc_assert (var->onepart);
4612 if (!var->n_var_parts)
4613 return NULL;
4615 VALUE_RECURSED_INTO (val) = true;
4617 for (node = var->var_part[0].loc_chain; node; node = node->next)
4618 if (MEM_P (node->loc)
4619 && MEM_EXPR (node->loc) == expr
4620 && INT_MEM_OFFSET (node->loc) == 0)
4622 where = node;
4623 break;
4625 else if (GET_CODE (node->loc) == VALUE
4626 && !VALUE_RECURSED_INTO (node->loc)
4627 && (where = find_mem_expr_in_1pdv (expr, node->loc, vars)))
4628 break;
4630 VALUE_RECURSED_INTO (val) = false;
4632 return where;
4635 /* Return TRUE if the value of MEM may vary across a call. */
4637 static bool
4638 mem_dies_at_call (rtx mem)
4640 tree expr = MEM_EXPR (mem);
4641 tree decl;
4643 if (!expr)
4644 return true;
4646 decl = get_base_address (expr);
4648 if (!decl)
4649 return true;
4651 if (!DECL_P (decl))
4652 return true;
4654 return (may_be_aliased (decl)
4655 || (!TREE_READONLY (decl) && is_global_var (decl)));
4658 /* Remove all MEMs from the location list of a hash table entry for a
4659 one-part variable, except those whose MEM attributes map back to
4660 the variable itself, directly or within a VALUE. */
4663 dataflow_set_preserve_mem_locs (variable **slot, dataflow_set *set)
4665 variable *var = *slot;
4667 if (var->onepart == ONEPART_VDECL || var->onepart == ONEPART_DEXPR)
4669 tree decl = dv_as_decl (var->dv);
4670 location_chain *loc, **locp;
4671 bool changed = false;
4673 if (!var->n_var_parts)
4674 return 1;
4676 gcc_assert (var->n_var_parts == 1);
4678 if (shared_var_p (var, set->vars))
4680 for (loc = var->var_part[0].loc_chain; loc; loc = loc->next)
4682 /* We want to remove dying MEMs that don't refer to DECL. */
4683 if (GET_CODE (loc->loc) == MEM
4684 && (MEM_EXPR (loc->loc) != decl
4685 || INT_MEM_OFFSET (loc->loc) != 0)
4686 && mem_dies_at_call (loc->loc))
4687 break;
4688 /* We want to move here MEMs that do refer to DECL. */
4689 else if (GET_CODE (loc->loc) == VALUE
4690 && find_mem_expr_in_1pdv (decl, loc->loc,
4691 shared_hash_htab (set->vars)))
4692 break;
4695 if (!loc)
4696 return 1;
4698 slot = unshare_variable (set, slot, var, VAR_INIT_STATUS_UNKNOWN);
4699 var = *slot;
4700 gcc_assert (var->n_var_parts == 1);
4703 for (locp = &var->var_part[0].loc_chain, loc = *locp;
4704 loc; loc = *locp)
4706 rtx old_loc = loc->loc;
4707 if (GET_CODE (old_loc) == VALUE)
4709 location_chain *mem_node
4710 = find_mem_expr_in_1pdv (decl, loc->loc,
4711 shared_hash_htab (set->vars));
4713 /* ??? This picks up only one out of multiple MEMs that
4714 refer to the same variable. Do we ever need to be
4715 concerned about dealing with more than one, or, given
4716 that they should all map to the same variable
4717 location, their addresses will have been merged and
4718 they will be regarded as equivalent? */
4719 if (mem_node)
4721 loc->loc = mem_node->loc;
4722 loc->set_src = mem_node->set_src;
4723 loc->init = MIN (loc->init, mem_node->init);
4727 if (GET_CODE (loc->loc) != MEM
4728 || (MEM_EXPR (loc->loc) == decl
4729 && INT_MEM_OFFSET (loc->loc) == 0)
4730 || !mem_dies_at_call (loc->loc))
4732 if (old_loc != loc->loc && emit_notes)
4734 if (old_loc == var->var_part[0].cur_loc)
4736 changed = true;
4737 var->var_part[0].cur_loc = NULL;
4740 locp = &loc->next;
4741 continue;
4744 if (emit_notes)
4746 if (old_loc == var->var_part[0].cur_loc)
4748 changed = true;
4749 var->var_part[0].cur_loc = NULL;
4752 *locp = loc->next;
4753 delete loc;
4756 if (!var->var_part[0].loc_chain)
4758 var->n_var_parts--;
4759 changed = true;
4761 if (changed)
4762 variable_was_changed (var, set);
4765 return 1;
4768 /* Remove all MEMs from the location list of a hash table entry for a
4769 onepart variable. */
4772 dataflow_set_remove_mem_locs (variable **slot, dataflow_set *set)
4774 variable *var = *slot;
4776 if (var->onepart != NOT_ONEPART)
4778 location_chain *loc, **locp;
4779 bool changed = false;
4780 rtx cur_loc;
4782 gcc_assert (var->n_var_parts == 1);
4784 if (shared_var_p (var, set->vars))
4786 for (loc = var->var_part[0].loc_chain; loc; loc = loc->next)
4787 if (GET_CODE (loc->loc) == MEM
4788 && mem_dies_at_call (loc->loc))
4789 break;
4791 if (!loc)
4792 return 1;
4794 slot = unshare_variable (set, slot, var, VAR_INIT_STATUS_UNKNOWN);
4795 var = *slot;
4796 gcc_assert (var->n_var_parts == 1);
4799 if (VAR_LOC_1PAUX (var))
4800 cur_loc = VAR_LOC_FROM (var);
4801 else
4802 cur_loc = var->var_part[0].cur_loc;
4804 for (locp = &var->var_part[0].loc_chain, loc = *locp;
4805 loc; loc = *locp)
4807 if (GET_CODE (loc->loc) != MEM
4808 || !mem_dies_at_call (loc->loc))
4810 locp = &loc->next;
4811 continue;
4814 *locp = loc->next;
4815 /* If we have deleted the location which was last emitted
4816 we have to emit new location so add the variable to set
4817 of changed variables. */
4818 if (cur_loc == loc->loc)
4820 changed = true;
4821 var->var_part[0].cur_loc = NULL;
4822 if (VAR_LOC_1PAUX (var))
4823 VAR_LOC_FROM (var) = NULL;
4825 delete loc;
4828 if (!var->var_part[0].loc_chain)
4830 var->n_var_parts--;
4831 changed = true;
4833 if (changed)
4834 variable_was_changed (var, set);
4837 return 1;
4840 /* Remove all variable-location information about call-clobbered
4841 registers, as well as associations between MEMs and VALUEs. */
4843 static void
4844 dataflow_set_clear_at_call (dataflow_set *set, rtx_insn *call_insn)
4846 unsigned int r;
4847 hard_reg_set_iterator hrsi;
4848 HARD_REG_SET invalidated_regs;
4850 get_call_reg_set_usage (call_insn, &invalidated_regs,
4851 regs_invalidated_by_call);
4853 EXECUTE_IF_SET_IN_HARD_REG_SET (invalidated_regs, 0, r, hrsi)
4854 var_regno_delete (set, r);
4856 if (MAY_HAVE_DEBUG_INSNS)
4858 set->traversed_vars = set->vars;
4859 shared_hash_htab (set->vars)
4860 ->traverse <dataflow_set *, dataflow_set_preserve_mem_locs> (set);
4861 set->traversed_vars = set->vars;
4862 shared_hash_htab (set->vars)
4863 ->traverse <dataflow_set *, dataflow_set_remove_mem_locs> (set);
4864 set->traversed_vars = NULL;
4868 static bool
4869 variable_part_different_p (variable_part *vp1, variable_part *vp2)
4871 location_chain *lc1, *lc2;
4873 for (lc1 = vp1->loc_chain; lc1; lc1 = lc1->next)
4875 for (lc2 = vp2->loc_chain; lc2; lc2 = lc2->next)
4877 if (REG_P (lc1->loc) && REG_P (lc2->loc))
4879 if (REGNO (lc1->loc) == REGNO (lc2->loc))
4880 break;
4882 if (rtx_equal_p (lc1->loc, lc2->loc))
4883 break;
4885 if (!lc2)
4886 return true;
4888 return false;
4891 /* Return true if one-part variables VAR1 and VAR2 are different.
4892 They must be in canonical order. */
4894 static bool
4895 onepart_variable_different_p (variable *var1, variable *var2)
4897 location_chain *lc1, *lc2;
4899 if (var1 == var2)
4900 return false;
4902 gcc_assert (var1->n_var_parts == 1
4903 && var2->n_var_parts == 1);
4905 lc1 = var1->var_part[0].loc_chain;
4906 lc2 = var2->var_part[0].loc_chain;
4908 gcc_assert (lc1 && lc2);
4910 while (lc1 && lc2)
4912 if (loc_cmp (lc1->loc, lc2->loc))
4913 return true;
4914 lc1 = lc1->next;
4915 lc2 = lc2->next;
4918 return lc1 != lc2;
4921 /* Return true if one-part variables VAR1 and VAR2 are different.
4922 They must be in canonical order. */
4924 static void
4925 dump_onepart_variable_differences (variable *var1, variable *var2)
4927 location_chain *lc1, *lc2;
4929 gcc_assert (var1 != var2);
4930 gcc_assert (dump_file);
4931 gcc_assert (dv_as_opaque (var1->dv) == dv_as_opaque (var2->dv));
4932 gcc_assert (var1->n_var_parts == 1
4933 && var2->n_var_parts == 1);
4935 lc1 = var1->var_part[0].loc_chain;
4936 lc2 = var2->var_part[0].loc_chain;
4938 gcc_assert (lc1 && lc2);
4940 while (lc1 && lc2)
4942 switch (loc_cmp (lc1->loc, lc2->loc))
4944 case -1:
4945 fprintf (dump_file, "removed: ");
4946 print_rtl_single (dump_file, lc1->loc);
4947 lc1 = lc1->next;
4948 continue;
4949 case 0:
4950 break;
4951 case 1:
4952 fprintf (dump_file, "added: ");
4953 print_rtl_single (dump_file, lc2->loc);
4954 lc2 = lc2->next;
4955 continue;
4956 default:
4957 gcc_unreachable ();
4959 lc1 = lc1->next;
4960 lc2 = lc2->next;
4963 while (lc1)
4965 fprintf (dump_file, "removed: ");
4966 print_rtl_single (dump_file, lc1->loc);
4967 lc1 = lc1->next;
4970 while (lc2)
4972 fprintf (dump_file, "added: ");
4973 print_rtl_single (dump_file, lc2->loc);
4974 lc2 = lc2->next;
4978 /* Return true if variables VAR1 and VAR2 are different. */
4980 static bool
4981 variable_different_p (variable *var1, variable *var2)
4983 int i;
4985 if (var1 == var2)
4986 return false;
4988 if (var1->onepart != var2->onepart)
4989 return true;
4991 if (var1->n_var_parts != var2->n_var_parts)
4992 return true;
4994 if (var1->onepart && var1->n_var_parts)
4996 gcc_checking_assert (dv_as_opaque (var1->dv) == dv_as_opaque (var2->dv)
4997 && var1->n_var_parts == 1);
4998 /* One-part values have locations in a canonical order. */
4999 return onepart_variable_different_p (var1, var2);
5002 for (i = 0; i < var1->n_var_parts; i++)
5004 if (VAR_PART_OFFSET (var1, i) != VAR_PART_OFFSET (var2, i))
5005 return true;
5006 if (variable_part_different_p (&var1->var_part[i], &var2->var_part[i]))
5007 return true;
5008 if (variable_part_different_p (&var2->var_part[i], &var1->var_part[i]))
5009 return true;
5011 return false;
5014 /* Return true if dataflow sets OLD_SET and NEW_SET differ. */
5016 static bool
5017 dataflow_set_different (dataflow_set *old_set, dataflow_set *new_set)
5019 variable_iterator_type hi;
5020 variable *var1;
5021 bool diffound = false;
5022 bool details = (dump_file && (dump_flags & TDF_DETAILS));
5024 #define RETRUE \
5025 do \
5027 if (!details) \
5028 return true; \
5029 else \
5030 diffound = true; \
5032 while (0)
5034 if (old_set->vars == new_set->vars)
5035 return false;
5037 if (shared_hash_htab (old_set->vars)->elements ()
5038 != shared_hash_htab (new_set->vars)->elements ())
5039 RETRUE;
5041 FOR_EACH_HASH_TABLE_ELEMENT (*shared_hash_htab (old_set->vars),
5042 var1, variable, hi)
5044 variable_table_type *htab = shared_hash_htab (new_set->vars);
5045 variable *var2 = htab->find_with_hash (var1->dv, dv_htab_hash (var1->dv));
5047 if (!var2)
5049 if (dump_file && (dump_flags & TDF_DETAILS))
5051 fprintf (dump_file, "dataflow difference found: removal of:\n");
5052 dump_var (var1);
5054 RETRUE;
5056 else if (variable_different_p (var1, var2))
5058 if (details)
5060 fprintf (dump_file, "dataflow difference found: "
5061 "old and new follow:\n");
5062 dump_var (var1);
5063 if (dv_onepart_p (var1->dv))
5064 dump_onepart_variable_differences (var1, var2);
5065 dump_var (var2);
5067 RETRUE;
5071 /* There's no need to traverse the second hashtab unless we want to
5072 print the details. If both have the same number of elements and
5073 the second one had all entries found in the first one, then the
5074 second can't have any extra entries. */
5075 if (!details)
5076 return diffound;
5078 FOR_EACH_HASH_TABLE_ELEMENT (*shared_hash_htab (new_set->vars),
5079 var1, variable, hi)
5081 variable_table_type *htab = shared_hash_htab (old_set->vars);
5082 variable *var2 = htab->find_with_hash (var1->dv, dv_htab_hash (var1->dv));
5083 if (!var2)
5085 if (details)
5087 fprintf (dump_file, "dataflow difference found: addition of:\n");
5088 dump_var (var1);
5090 RETRUE;
5094 #undef RETRUE
5096 return diffound;
5099 /* Free the contents of dataflow set SET. */
5101 static void
5102 dataflow_set_destroy (dataflow_set *set)
5104 int i;
5106 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
5107 attrs_list_clear (&set->regs[i]);
5109 shared_hash_destroy (set->vars);
5110 set->vars = NULL;
5113 /* Return true if T is a tracked parameter with non-degenerate record type. */
5115 static bool
5116 tracked_record_parameter_p (tree t)
5118 if (TREE_CODE (t) != PARM_DECL)
5119 return false;
5121 if (DECL_MODE (t) == BLKmode)
5122 return false;
5124 tree type = TREE_TYPE (t);
5125 if (TREE_CODE (type) != RECORD_TYPE)
5126 return false;
5128 if (TYPE_FIELDS (type) == NULL_TREE
5129 || DECL_CHAIN (TYPE_FIELDS (type)) == NULL_TREE)
5130 return false;
5132 return true;
5135 /* Shall EXPR be tracked? */
5137 static bool
5138 track_expr_p (tree expr, bool need_rtl)
5140 rtx decl_rtl;
5141 tree realdecl;
5143 if (TREE_CODE (expr) == DEBUG_EXPR_DECL)
5144 return DECL_RTL_SET_P (expr);
5146 /* If EXPR is not a parameter or a variable do not track it. */
5147 if (!VAR_P (expr) && TREE_CODE (expr) != PARM_DECL)
5148 return 0;
5150 /* It also must have a name... */
5151 if (!DECL_NAME (expr) && need_rtl)
5152 return 0;
5154 /* ... and a RTL assigned to it. */
5155 decl_rtl = DECL_RTL_IF_SET (expr);
5156 if (!decl_rtl && need_rtl)
5157 return 0;
5159 /* If this expression is really a debug alias of some other declaration, we
5160 don't need to track this expression if the ultimate declaration is
5161 ignored. */
5162 realdecl = expr;
5163 if (VAR_P (realdecl) && DECL_HAS_DEBUG_EXPR_P (realdecl))
5165 realdecl = DECL_DEBUG_EXPR (realdecl);
5166 if (!DECL_P (realdecl))
5168 if (handled_component_p (realdecl)
5169 || (TREE_CODE (realdecl) == MEM_REF
5170 && TREE_CODE (TREE_OPERAND (realdecl, 0)) == ADDR_EXPR))
5172 HOST_WIDE_INT bitsize, bitpos, maxsize;
5173 bool reverse;
5174 tree innerdecl
5175 = get_ref_base_and_extent (realdecl, &bitpos, &bitsize,
5176 &maxsize, &reverse);
5177 if (!DECL_P (innerdecl)
5178 || DECL_IGNORED_P (innerdecl)
5179 /* Do not track declarations for parts of tracked record
5180 parameters since we want to track them as a whole. */
5181 || tracked_record_parameter_p (innerdecl)
5182 || TREE_STATIC (innerdecl)
5183 || bitsize <= 0
5184 || bitpos + bitsize > 256
5185 || bitsize != maxsize)
5186 return 0;
5187 else
5188 realdecl = expr;
5190 else
5191 return 0;
5195 /* Do not track EXPR if REALDECL it should be ignored for debugging
5196 purposes. */
5197 if (DECL_IGNORED_P (realdecl))
5198 return 0;
5200 /* Do not track global variables until we are able to emit correct location
5201 list for them. */
5202 if (TREE_STATIC (realdecl))
5203 return 0;
5205 /* When the EXPR is a DECL for alias of some variable (see example)
5206 the TREE_STATIC flag is not used. Disable tracking all DECLs whose
5207 DECL_RTL contains SYMBOL_REF.
5209 Example:
5210 extern char **_dl_argv_internal __attribute__ ((alias ("_dl_argv")));
5211 char **_dl_argv;
5213 if (decl_rtl && MEM_P (decl_rtl)
5214 && contains_symbol_ref_p (XEXP (decl_rtl, 0)))
5215 return 0;
5217 /* If RTX is a memory it should not be very large (because it would be
5218 an array or struct). */
5219 if (decl_rtl && MEM_P (decl_rtl))
5221 /* Do not track structures and arrays. */
5222 if (GET_MODE (decl_rtl) == BLKmode
5223 || AGGREGATE_TYPE_P (TREE_TYPE (realdecl)))
5224 return 0;
5225 if (MEM_SIZE_KNOWN_P (decl_rtl)
5226 && MEM_SIZE (decl_rtl) > MAX_VAR_PARTS)
5227 return 0;
5230 DECL_CHANGED (expr) = 0;
5231 DECL_CHANGED (realdecl) = 0;
5232 return 1;
5235 /* Determine whether a given LOC refers to the same variable part as
5236 EXPR+OFFSET. */
5238 static bool
5239 same_variable_part_p (rtx loc, tree expr, HOST_WIDE_INT offset)
5241 tree expr2;
5242 HOST_WIDE_INT offset2;
5244 if (! DECL_P (expr))
5245 return false;
5247 if (REG_P (loc))
5249 expr2 = REG_EXPR (loc);
5250 offset2 = REG_OFFSET (loc);
5252 else if (MEM_P (loc))
5254 expr2 = MEM_EXPR (loc);
5255 offset2 = INT_MEM_OFFSET (loc);
5257 else
5258 return false;
5260 if (! expr2 || ! DECL_P (expr2))
5261 return false;
5263 expr = var_debug_decl (expr);
5264 expr2 = var_debug_decl (expr2);
5266 return (expr == expr2 && offset == offset2);
5269 /* LOC is a REG or MEM that we would like to track if possible.
5270 If EXPR is null, we don't know what expression LOC refers to,
5271 otherwise it refers to EXPR + OFFSET. STORE_REG_P is true if
5272 LOC is an lvalue register.
5274 Return true if EXPR is nonnull and if LOC, or some lowpart of it,
5275 is something we can track. When returning true, store the mode of
5276 the lowpart we can track in *MODE_OUT (if nonnull) and its offset
5277 from EXPR in *OFFSET_OUT (if nonnull). */
5279 static bool
5280 track_loc_p (rtx loc, tree expr, HOST_WIDE_INT offset, bool store_reg_p,
5281 machine_mode *mode_out, HOST_WIDE_INT *offset_out)
5283 machine_mode mode;
5285 if (expr == NULL || !track_expr_p (expr, true))
5286 return false;
5288 /* If REG was a paradoxical subreg, its REG_ATTRS will describe the
5289 whole subreg, but only the old inner part is really relevant. */
5290 mode = GET_MODE (loc);
5291 if (REG_P (loc) && !HARD_REGISTER_NUM_P (ORIGINAL_REGNO (loc)))
5293 machine_mode pseudo_mode;
5295 pseudo_mode = PSEUDO_REGNO_MODE (ORIGINAL_REGNO (loc));
5296 if (GET_MODE_SIZE (mode) > GET_MODE_SIZE (pseudo_mode))
5298 offset += byte_lowpart_offset (pseudo_mode, mode);
5299 mode = pseudo_mode;
5303 /* If LOC is a paradoxical lowpart of EXPR, refer to EXPR itself.
5304 Do the same if we are storing to a register and EXPR occupies
5305 the whole of register LOC; in that case, the whole of EXPR is
5306 being changed. We exclude complex modes from the second case
5307 because the real and imaginary parts are represented as separate
5308 pseudo registers, even if the whole complex value fits into one
5309 hard register. */
5310 if ((GET_MODE_SIZE (mode) > GET_MODE_SIZE (DECL_MODE (expr))
5311 || (store_reg_p
5312 && !COMPLEX_MODE_P (DECL_MODE (expr))
5313 && hard_regno_nregs[REGNO (loc)][DECL_MODE (expr)] == 1))
5314 && offset + byte_lowpart_offset (DECL_MODE (expr), mode) == 0)
5316 mode = DECL_MODE (expr);
5317 offset = 0;
5320 if (offset < 0 || offset >= MAX_VAR_PARTS)
5321 return false;
5323 if (mode_out)
5324 *mode_out = mode;
5325 if (offset_out)
5326 *offset_out = offset;
5327 return true;
5330 /* Return the MODE lowpart of LOC, or null if LOC is not something we
5331 want to track. When returning nonnull, make sure that the attributes
5332 on the returned value are updated. */
5334 static rtx
5335 var_lowpart (machine_mode mode, rtx loc)
5337 unsigned int offset, reg_offset, regno;
5339 if (GET_MODE (loc) == mode)
5340 return loc;
5342 if (!REG_P (loc) && !MEM_P (loc))
5343 return NULL;
5345 offset = byte_lowpart_offset (mode, GET_MODE (loc));
5347 if (MEM_P (loc))
5348 return adjust_address_nv (loc, mode, offset);
5350 reg_offset = subreg_lowpart_offset (mode, GET_MODE (loc));
5351 regno = REGNO (loc) + subreg_regno_offset (REGNO (loc), GET_MODE (loc),
5352 reg_offset, mode);
5353 return gen_rtx_REG_offset (loc, mode, regno, offset);
5356 /* Carry information about uses and stores while walking rtx. */
5358 struct count_use_info
5360 /* The insn where the RTX is. */
5361 rtx_insn *insn;
5363 /* The basic block where insn is. */
5364 basic_block bb;
5366 /* The array of n_sets sets in the insn, as determined by cselib. */
5367 struct cselib_set *sets;
5368 int n_sets;
5370 /* True if we're counting stores, false otherwise. */
5371 bool store_p;
5374 /* Find a VALUE corresponding to X. */
5376 static inline cselib_val *
5377 find_use_val (rtx x, machine_mode mode, struct count_use_info *cui)
5379 int i;
5381 if (cui->sets)
5383 /* This is called after uses are set up and before stores are
5384 processed by cselib, so it's safe to look up srcs, but not
5385 dsts. So we look up expressions that appear in srcs or in
5386 dest expressions, but we search the sets array for dests of
5387 stores. */
5388 if (cui->store_p)
5390 /* Some targets represent memset and memcpy patterns
5391 by (set (mem:BLK ...) (reg:[QHSD]I ...)) or
5392 (set (mem:BLK ...) (const_int ...)) or
5393 (set (mem:BLK ...) (mem:BLK ...)). Don't return anything
5394 in that case, otherwise we end up with mode mismatches. */
5395 if (mode == BLKmode && MEM_P (x))
5396 return NULL;
5397 for (i = 0; i < cui->n_sets; i++)
5398 if (cui->sets[i].dest == x)
5399 return cui->sets[i].src_elt;
5401 else
5402 return cselib_lookup (x, mode, 0, VOIDmode);
5405 return NULL;
5408 /* Replace all registers and addresses in an expression with VALUE
5409 expressions that map back to them, unless the expression is a
5410 register. If no mapping is or can be performed, returns NULL. */
5412 static rtx
5413 replace_expr_with_values (rtx loc)
5415 if (REG_P (loc) || GET_CODE (loc) == ENTRY_VALUE)
5416 return NULL;
5417 else if (MEM_P (loc))
5419 cselib_val *addr = cselib_lookup (XEXP (loc, 0),
5420 get_address_mode (loc), 0,
5421 GET_MODE (loc));
5422 if (addr)
5423 return replace_equiv_address_nv (loc, addr->val_rtx);
5424 else
5425 return NULL;
5427 else
5428 return cselib_subst_to_values (loc, VOIDmode);
5431 /* Return true if X contains a DEBUG_EXPR. */
5433 static bool
5434 rtx_debug_expr_p (const_rtx x)
5436 subrtx_iterator::array_type array;
5437 FOR_EACH_SUBRTX (iter, array, x, ALL)
5438 if (GET_CODE (*iter) == DEBUG_EXPR)
5439 return true;
5440 return false;
5443 /* Determine what kind of micro operation to choose for a USE. Return
5444 MO_CLOBBER if no micro operation is to be generated. */
5446 static enum micro_operation_type
5447 use_type (rtx loc, struct count_use_info *cui, machine_mode *modep)
5449 tree expr;
5451 if (cui && cui->sets)
5453 if (GET_CODE (loc) == VAR_LOCATION)
5455 if (track_expr_p (PAT_VAR_LOCATION_DECL (loc), false))
5457 rtx ploc = PAT_VAR_LOCATION_LOC (loc);
5458 if (! VAR_LOC_UNKNOWN_P (ploc))
5460 cselib_val *val = cselib_lookup (ploc, GET_MODE (loc), 1,
5461 VOIDmode);
5463 /* ??? flag_float_store and volatile mems are never
5464 given values, but we could in theory use them for
5465 locations. */
5466 gcc_assert (val || 1);
5468 return MO_VAL_LOC;
5470 else
5471 return MO_CLOBBER;
5474 if (REG_P (loc) || MEM_P (loc))
5476 if (modep)
5477 *modep = GET_MODE (loc);
5478 if (cui->store_p)
5480 if (REG_P (loc)
5481 || (find_use_val (loc, GET_MODE (loc), cui)
5482 && cselib_lookup (XEXP (loc, 0),
5483 get_address_mode (loc), 0,
5484 GET_MODE (loc))))
5485 return MO_VAL_SET;
5487 else
5489 cselib_val *val = find_use_val (loc, GET_MODE (loc), cui);
5491 if (val && !cselib_preserved_value_p (val))
5492 return MO_VAL_USE;
5497 if (REG_P (loc))
5499 gcc_assert (REGNO (loc) < FIRST_PSEUDO_REGISTER);
5501 if (loc == cfa_base_rtx)
5502 return MO_CLOBBER;
5503 expr = REG_EXPR (loc);
5505 if (!expr)
5506 return MO_USE_NO_VAR;
5507 else if (target_for_debug_bind (var_debug_decl (expr)))
5508 return MO_CLOBBER;
5509 else if (track_loc_p (loc, expr, REG_OFFSET (loc),
5510 false, modep, NULL))
5511 return MO_USE;
5512 else
5513 return MO_USE_NO_VAR;
5515 else if (MEM_P (loc))
5517 expr = MEM_EXPR (loc);
5519 if (!expr)
5520 return MO_CLOBBER;
5521 else if (target_for_debug_bind (var_debug_decl (expr)))
5522 return MO_CLOBBER;
5523 else if (track_loc_p (loc, expr, INT_MEM_OFFSET (loc),
5524 false, modep, NULL)
5525 /* Multi-part variables shouldn't refer to one-part
5526 variable names such as VALUEs (never happens) or
5527 DEBUG_EXPRs (only happens in the presence of debug
5528 insns). */
5529 && (!MAY_HAVE_DEBUG_INSNS
5530 || !rtx_debug_expr_p (XEXP (loc, 0))))
5531 return MO_USE;
5532 else
5533 return MO_CLOBBER;
5536 return MO_CLOBBER;
5539 /* Log to OUT information about micro-operation MOPT involving X in
5540 INSN of BB. */
5542 static inline void
5543 log_op_type (rtx x, basic_block bb, rtx_insn *insn,
5544 enum micro_operation_type mopt, FILE *out)
5546 fprintf (out, "bb %i op %i insn %i %s ",
5547 bb->index, VTI (bb)->mos.length (),
5548 INSN_UID (insn), micro_operation_type_name[mopt]);
5549 print_inline_rtx (out, x, 2);
5550 fputc ('\n', out);
5553 /* Tell whether the CONCAT used to holds a VALUE and its location
5554 needs value resolution, i.e., an attempt of mapping the location
5555 back to other incoming values. */
5556 #define VAL_NEEDS_RESOLUTION(x) \
5557 (RTL_FLAG_CHECK1 ("VAL_NEEDS_RESOLUTION", (x), CONCAT)->volatil)
5558 /* Whether the location in the CONCAT is a tracked expression, that
5559 should also be handled like a MO_USE. */
5560 #define VAL_HOLDS_TRACK_EXPR(x) \
5561 (RTL_FLAG_CHECK1 ("VAL_HOLDS_TRACK_EXPR", (x), CONCAT)->used)
5562 /* Whether the location in the CONCAT should be handled like a MO_COPY
5563 as well. */
5564 #define VAL_EXPR_IS_COPIED(x) \
5565 (RTL_FLAG_CHECK1 ("VAL_EXPR_IS_COPIED", (x), CONCAT)->jump)
5566 /* Whether the location in the CONCAT should be handled like a
5567 MO_CLOBBER as well. */
5568 #define VAL_EXPR_IS_CLOBBERED(x) \
5569 (RTL_FLAG_CHECK1 ("VAL_EXPR_IS_CLOBBERED", (x), CONCAT)->unchanging)
5571 /* All preserved VALUEs. */
5572 static vec<rtx> preserved_values;
5574 /* Ensure VAL is preserved and remember it in a vector for vt_emit_notes. */
5576 static void
5577 preserve_value (cselib_val *val)
5579 cselib_preserve_value (val);
5580 preserved_values.safe_push (val->val_rtx);
5583 /* Helper function for MO_VAL_LOC handling. Return non-zero if
5584 any rtxes not suitable for CONST use not replaced by VALUEs
5585 are discovered. */
5587 static bool
5588 non_suitable_const (const_rtx x)
5590 subrtx_iterator::array_type array;
5591 FOR_EACH_SUBRTX (iter, array, x, ALL)
5593 const_rtx x = *iter;
5594 switch (GET_CODE (x))
5596 case REG:
5597 case DEBUG_EXPR:
5598 case PC:
5599 case SCRATCH:
5600 case CC0:
5601 case ASM_INPUT:
5602 case ASM_OPERANDS:
5603 return true;
5604 case MEM:
5605 if (!MEM_READONLY_P (x))
5606 return true;
5607 break;
5608 default:
5609 break;
5612 return false;
5615 /* Add uses (register and memory references) LOC which will be tracked
5616 to VTI (bb)->mos. */
5618 static void
5619 add_uses (rtx loc, struct count_use_info *cui)
5621 machine_mode mode = VOIDmode;
5622 enum micro_operation_type type = use_type (loc, cui, &mode);
5624 if (type != MO_CLOBBER)
5626 basic_block bb = cui->bb;
5627 micro_operation mo;
5629 mo.type = type;
5630 mo.u.loc = type == MO_USE ? var_lowpart (mode, loc) : loc;
5631 mo.insn = cui->insn;
5633 if (type == MO_VAL_LOC)
5635 rtx oloc = loc;
5636 rtx vloc = PAT_VAR_LOCATION_LOC (oloc);
5637 cselib_val *val;
5639 gcc_assert (cui->sets);
5641 if (MEM_P (vloc)
5642 && !REG_P (XEXP (vloc, 0))
5643 && !MEM_P (XEXP (vloc, 0)))
5645 rtx mloc = vloc;
5646 machine_mode address_mode = get_address_mode (mloc);
5647 cselib_val *val
5648 = cselib_lookup (XEXP (mloc, 0), address_mode, 0,
5649 GET_MODE (mloc));
5651 if (val && !cselib_preserved_value_p (val))
5652 preserve_value (val);
5655 if (CONSTANT_P (vloc)
5656 && (GET_CODE (vloc) != CONST || non_suitable_const (vloc)))
5657 /* For constants don't look up any value. */;
5658 else if (!VAR_LOC_UNKNOWN_P (vloc) && !unsuitable_loc (vloc)
5659 && (val = find_use_val (vloc, GET_MODE (oloc), cui)))
5661 machine_mode mode2;
5662 enum micro_operation_type type2;
5663 rtx nloc = NULL;
5664 bool resolvable = REG_P (vloc) || MEM_P (vloc);
5666 if (resolvable)
5667 nloc = replace_expr_with_values (vloc);
5669 if (nloc)
5671 oloc = shallow_copy_rtx (oloc);
5672 PAT_VAR_LOCATION_LOC (oloc) = nloc;
5675 oloc = gen_rtx_CONCAT (mode, val->val_rtx, oloc);
5677 type2 = use_type (vloc, 0, &mode2);
5679 gcc_assert (type2 == MO_USE || type2 == MO_USE_NO_VAR
5680 || type2 == MO_CLOBBER);
5682 if (type2 == MO_CLOBBER
5683 && !cselib_preserved_value_p (val))
5685 VAL_NEEDS_RESOLUTION (oloc) = resolvable;
5686 preserve_value (val);
5689 else if (!VAR_LOC_UNKNOWN_P (vloc))
5691 oloc = shallow_copy_rtx (oloc);
5692 PAT_VAR_LOCATION_LOC (oloc) = gen_rtx_UNKNOWN_VAR_LOC ();
5695 mo.u.loc = oloc;
5697 else if (type == MO_VAL_USE)
5699 machine_mode mode2 = VOIDmode;
5700 enum micro_operation_type type2;
5701 cselib_val *val = find_use_val (loc, GET_MODE (loc), cui);
5702 rtx vloc, oloc = loc, nloc;
5704 gcc_assert (cui->sets);
5706 if (MEM_P (oloc)
5707 && !REG_P (XEXP (oloc, 0))
5708 && !MEM_P (XEXP (oloc, 0)))
5710 rtx mloc = oloc;
5711 machine_mode address_mode = get_address_mode (mloc);
5712 cselib_val *val
5713 = cselib_lookup (XEXP (mloc, 0), address_mode, 0,
5714 GET_MODE (mloc));
5716 if (val && !cselib_preserved_value_p (val))
5717 preserve_value (val);
5720 type2 = use_type (loc, 0, &mode2);
5722 gcc_assert (type2 == MO_USE || type2 == MO_USE_NO_VAR
5723 || type2 == MO_CLOBBER);
5725 if (type2 == MO_USE)
5726 vloc = var_lowpart (mode2, loc);
5727 else
5728 vloc = oloc;
5730 /* The loc of a MO_VAL_USE may have two forms:
5732 (concat val src): val is at src, a value-based
5733 representation.
5735 (concat (concat val use) src): same as above, with use as
5736 the MO_USE tracked value, if it differs from src.
5740 gcc_checking_assert (REG_P (loc) || MEM_P (loc));
5741 nloc = replace_expr_with_values (loc);
5742 if (!nloc)
5743 nloc = oloc;
5745 if (vloc != nloc)
5746 oloc = gen_rtx_CONCAT (mode2, val->val_rtx, vloc);
5747 else
5748 oloc = val->val_rtx;
5750 mo.u.loc = gen_rtx_CONCAT (mode, oloc, nloc);
5752 if (type2 == MO_USE)
5753 VAL_HOLDS_TRACK_EXPR (mo.u.loc) = 1;
5754 if (!cselib_preserved_value_p (val))
5756 VAL_NEEDS_RESOLUTION (mo.u.loc) = 1;
5757 preserve_value (val);
5760 else
5761 gcc_assert (type == MO_USE || type == MO_USE_NO_VAR);
5763 if (dump_file && (dump_flags & TDF_DETAILS))
5764 log_op_type (mo.u.loc, cui->bb, cui->insn, mo.type, dump_file);
5765 VTI (bb)->mos.safe_push (mo);
5769 /* Helper function for finding all uses of REG/MEM in X in insn INSN. */
5771 static void
5772 add_uses_1 (rtx *x, void *cui)
5774 subrtx_var_iterator::array_type array;
5775 FOR_EACH_SUBRTX_VAR (iter, array, *x, NONCONST)
5776 add_uses (*iter, (struct count_use_info *) cui);
5779 /* This is the value used during expansion of locations. We want it
5780 to be unbounded, so that variables expanded deep in a recursion
5781 nest are fully evaluated, so that their values are cached
5782 correctly. We avoid recursion cycles through other means, and we
5783 don't unshare RTL, so excess complexity is not a problem. */
5784 #define EXPR_DEPTH (INT_MAX)
5785 /* We use this to keep too-complex expressions from being emitted as
5786 location notes, and then to debug information. Users can trade
5787 compile time for ridiculously complex expressions, although they're
5788 seldom useful, and they may often have to be discarded as not
5789 representable anyway. */
5790 #define EXPR_USE_DEPTH (PARAM_VALUE (PARAM_MAX_VARTRACK_EXPR_DEPTH))
5792 /* Attempt to reverse the EXPR operation in the debug info and record
5793 it in the cselib table. Say for reg1 = reg2 + 6 even when reg2 is
5794 no longer live we can express its value as VAL - 6. */
5796 static void
5797 reverse_op (rtx val, const_rtx expr, rtx_insn *insn)
5799 rtx src, arg, ret;
5800 cselib_val *v;
5801 struct elt_loc_list *l;
5802 enum rtx_code code;
5803 int count;
5805 if (GET_CODE (expr) != SET)
5806 return;
5808 if (!REG_P (SET_DEST (expr)) || GET_MODE (val) != GET_MODE (SET_DEST (expr)))
5809 return;
5811 src = SET_SRC (expr);
5812 switch (GET_CODE (src))
5814 case PLUS:
5815 case MINUS:
5816 case XOR:
5817 case NOT:
5818 case NEG:
5819 if (!REG_P (XEXP (src, 0)))
5820 return;
5821 break;
5822 case SIGN_EXTEND:
5823 case ZERO_EXTEND:
5824 if (!REG_P (XEXP (src, 0)) && !MEM_P (XEXP (src, 0)))
5825 return;
5826 break;
5827 default:
5828 return;
5831 if (!SCALAR_INT_MODE_P (GET_MODE (src)) || XEXP (src, 0) == cfa_base_rtx)
5832 return;
5834 v = cselib_lookup (XEXP (src, 0), GET_MODE (XEXP (src, 0)), 0, VOIDmode);
5835 if (!v || !cselib_preserved_value_p (v))
5836 return;
5838 /* Use canonical V to avoid creating multiple redundant expressions
5839 for different VALUES equivalent to V. */
5840 v = canonical_cselib_val (v);
5842 /* Adding a reverse op isn't useful if V already has an always valid
5843 location. Ignore ENTRY_VALUE, while it is always constant, we should
5844 prefer non-ENTRY_VALUE locations whenever possible. */
5845 for (l = v->locs, count = 0; l; l = l->next, count++)
5846 if (CONSTANT_P (l->loc)
5847 && (GET_CODE (l->loc) != CONST || !references_value_p (l->loc, 0)))
5848 return;
5849 /* Avoid creating too large locs lists. */
5850 else if (count == PARAM_VALUE (PARAM_MAX_VARTRACK_REVERSE_OP_SIZE))
5851 return;
5853 switch (GET_CODE (src))
5855 case NOT:
5856 case NEG:
5857 if (GET_MODE (v->val_rtx) != GET_MODE (val))
5858 return;
5859 ret = gen_rtx_fmt_e (GET_CODE (src), GET_MODE (val), val);
5860 break;
5861 case SIGN_EXTEND:
5862 case ZERO_EXTEND:
5863 ret = gen_lowpart_SUBREG (GET_MODE (v->val_rtx), val);
5864 break;
5865 case XOR:
5866 code = XOR;
5867 goto binary;
5868 case PLUS:
5869 code = MINUS;
5870 goto binary;
5871 case MINUS:
5872 code = PLUS;
5873 goto binary;
5874 binary:
5875 if (GET_MODE (v->val_rtx) != GET_MODE (val))
5876 return;
5877 arg = XEXP (src, 1);
5878 if (!CONST_INT_P (arg) && GET_CODE (arg) != SYMBOL_REF)
5880 arg = cselib_expand_value_rtx (arg, scratch_regs, 5);
5881 if (arg == NULL_RTX)
5882 return;
5883 if (!CONST_INT_P (arg) && GET_CODE (arg) != SYMBOL_REF)
5884 return;
5886 ret = simplify_gen_binary (code, GET_MODE (val), val, arg);
5887 break;
5888 default:
5889 gcc_unreachable ();
5892 cselib_add_permanent_equiv (v, ret, insn);
5895 /* Add stores (register and memory references) LOC which will be tracked
5896 to VTI (bb)->mos. EXPR is the RTL expression containing the store.
5897 CUIP->insn is instruction which the LOC is part of. */
5899 static void
5900 add_stores (rtx loc, const_rtx expr, void *cuip)
5902 machine_mode mode = VOIDmode, mode2;
5903 struct count_use_info *cui = (struct count_use_info *)cuip;
5904 basic_block bb = cui->bb;
5905 micro_operation mo;
5906 rtx oloc = loc, nloc, src = NULL;
5907 enum micro_operation_type type = use_type (loc, cui, &mode);
5908 bool track_p = false;
5909 cselib_val *v;
5910 bool resolve, preserve;
5912 if (type == MO_CLOBBER)
5913 return;
5915 mode2 = mode;
5917 if (REG_P (loc))
5919 gcc_assert (loc != cfa_base_rtx);
5920 if ((GET_CODE (expr) == CLOBBER && type != MO_VAL_SET)
5921 || !(track_p = use_type (loc, NULL, &mode2) == MO_USE)
5922 || GET_CODE (expr) == CLOBBER)
5924 mo.type = MO_CLOBBER;
5925 mo.u.loc = loc;
5926 if (GET_CODE (expr) == SET
5927 && SET_DEST (expr) == loc
5928 && !unsuitable_loc (SET_SRC (expr))
5929 && find_use_val (loc, mode, cui))
5931 gcc_checking_assert (type == MO_VAL_SET);
5932 mo.u.loc = gen_rtx_SET (loc, SET_SRC (expr));
5935 else
5937 if (GET_CODE (expr) == SET
5938 && SET_DEST (expr) == loc
5939 && GET_CODE (SET_SRC (expr)) != ASM_OPERANDS)
5940 src = var_lowpart (mode2, SET_SRC (expr));
5941 loc = var_lowpart (mode2, loc);
5943 if (src == NULL)
5945 mo.type = MO_SET;
5946 mo.u.loc = loc;
5948 else
5950 rtx xexpr = gen_rtx_SET (loc, src);
5951 if (same_variable_part_p (src, REG_EXPR (loc), REG_OFFSET (loc)))
5953 /* If this is an instruction copying (part of) a parameter
5954 passed by invisible reference to its register location,
5955 pretend it's a SET so that the initial memory location
5956 is discarded, as the parameter register can be reused
5957 for other purposes and we do not track locations based
5958 on generic registers. */
5959 if (MEM_P (src)
5960 && REG_EXPR (loc)
5961 && TREE_CODE (REG_EXPR (loc)) == PARM_DECL
5962 && DECL_MODE (REG_EXPR (loc)) != BLKmode
5963 && MEM_P (DECL_INCOMING_RTL (REG_EXPR (loc)))
5964 && XEXP (DECL_INCOMING_RTL (REG_EXPR (loc)), 0)
5965 != arg_pointer_rtx)
5966 mo.type = MO_SET;
5967 else
5968 mo.type = MO_COPY;
5970 else
5971 mo.type = MO_SET;
5972 mo.u.loc = xexpr;
5975 mo.insn = cui->insn;
5977 else if (MEM_P (loc)
5978 && ((track_p = use_type (loc, NULL, &mode2) == MO_USE)
5979 || cui->sets))
5981 if (MEM_P (loc) && type == MO_VAL_SET
5982 && !REG_P (XEXP (loc, 0))
5983 && !MEM_P (XEXP (loc, 0)))
5985 rtx mloc = loc;
5986 machine_mode address_mode = get_address_mode (mloc);
5987 cselib_val *val = cselib_lookup (XEXP (mloc, 0),
5988 address_mode, 0,
5989 GET_MODE (mloc));
5991 if (val && !cselib_preserved_value_p (val))
5992 preserve_value (val);
5995 if (GET_CODE (expr) == CLOBBER || !track_p)
5997 mo.type = MO_CLOBBER;
5998 mo.u.loc = track_p ? var_lowpart (mode2, loc) : loc;
6000 else
6002 if (GET_CODE (expr) == SET
6003 && SET_DEST (expr) == loc
6004 && GET_CODE (SET_SRC (expr)) != ASM_OPERANDS)
6005 src = var_lowpart (mode2, SET_SRC (expr));
6006 loc = var_lowpart (mode2, loc);
6008 if (src == NULL)
6010 mo.type = MO_SET;
6011 mo.u.loc = loc;
6013 else
6015 rtx xexpr = gen_rtx_SET (loc, src);
6016 if (same_variable_part_p (SET_SRC (xexpr),
6017 MEM_EXPR (loc),
6018 INT_MEM_OFFSET (loc)))
6019 mo.type = MO_COPY;
6020 else
6021 mo.type = MO_SET;
6022 mo.u.loc = xexpr;
6025 mo.insn = cui->insn;
6027 else
6028 return;
6030 if (type != MO_VAL_SET)
6031 goto log_and_return;
6033 v = find_use_val (oloc, mode, cui);
6035 if (!v)
6036 goto log_and_return;
6038 resolve = preserve = !cselib_preserved_value_p (v);
6040 /* We cannot track values for multiple-part variables, so we track only
6041 locations for tracked record parameters. */
6042 if (track_p
6043 && REG_P (loc)
6044 && REG_EXPR (loc)
6045 && tracked_record_parameter_p (REG_EXPR (loc)))
6047 /* Although we don't use the value here, it could be used later by the
6048 mere virtue of its existence as the operand of the reverse operation
6049 that gave rise to it (typically extension/truncation). Make sure it
6050 is preserved as required by vt_expand_var_loc_chain. */
6051 if (preserve)
6052 preserve_value (v);
6053 goto log_and_return;
6056 if (loc == stack_pointer_rtx
6057 && hard_frame_pointer_adjustment != -1
6058 && preserve)
6059 cselib_set_value_sp_based (v);
6061 nloc = replace_expr_with_values (oloc);
6062 if (nloc)
6063 oloc = nloc;
6065 if (GET_CODE (PATTERN (cui->insn)) == COND_EXEC)
6067 cselib_val *oval = cselib_lookup (oloc, GET_MODE (oloc), 0, VOIDmode);
6069 if (oval == v)
6070 return;
6071 gcc_assert (REG_P (oloc) || MEM_P (oloc));
6073 if (oval && !cselib_preserved_value_p (oval))
6075 micro_operation moa;
6077 preserve_value (oval);
6079 moa.type = MO_VAL_USE;
6080 moa.u.loc = gen_rtx_CONCAT (mode, oval->val_rtx, oloc);
6081 VAL_NEEDS_RESOLUTION (moa.u.loc) = 1;
6082 moa.insn = cui->insn;
6084 if (dump_file && (dump_flags & TDF_DETAILS))
6085 log_op_type (moa.u.loc, cui->bb, cui->insn,
6086 moa.type, dump_file);
6087 VTI (bb)->mos.safe_push (moa);
6090 resolve = false;
6092 else if (resolve && GET_CODE (mo.u.loc) == SET)
6094 if (REG_P (SET_SRC (expr)) || MEM_P (SET_SRC (expr)))
6095 nloc = replace_expr_with_values (SET_SRC (expr));
6096 else
6097 nloc = NULL_RTX;
6099 /* Avoid the mode mismatch between oexpr and expr. */
6100 if (!nloc && mode != mode2)
6102 nloc = SET_SRC (expr);
6103 gcc_assert (oloc == SET_DEST (expr));
6106 if (nloc && nloc != SET_SRC (mo.u.loc))
6107 oloc = gen_rtx_SET (oloc, nloc);
6108 else
6110 if (oloc == SET_DEST (mo.u.loc))
6111 /* No point in duplicating. */
6112 oloc = mo.u.loc;
6113 if (!REG_P (SET_SRC (mo.u.loc)))
6114 resolve = false;
6117 else if (!resolve)
6119 if (GET_CODE (mo.u.loc) == SET
6120 && oloc == SET_DEST (mo.u.loc))
6121 /* No point in duplicating. */
6122 oloc = mo.u.loc;
6124 else
6125 resolve = false;
6127 loc = gen_rtx_CONCAT (mode, v->val_rtx, oloc);
6129 if (mo.u.loc != oloc)
6130 loc = gen_rtx_CONCAT (GET_MODE (mo.u.loc), loc, mo.u.loc);
6132 /* The loc of a MO_VAL_SET may have various forms:
6134 (concat val dst): dst now holds val
6136 (concat val (set dst src)): dst now holds val, copied from src
6138 (concat (concat val dstv) dst): dst now holds val; dstv is dst
6139 after replacing mems and non-top-level regs with values.
6141 (concat (concat val dstv) (set dst src)): dst now holds val,
6142 copied from src. dstv is a value-based representation of dst, if
6143 it differs from dst. If resolution is needed, src is a REG, and
6144 its mode is the same as that of val.
6146 (concat (concat val (set dstv srcv)) (set dst src)): src
6147 copied to dst, holding val. dstv and srcv are value-based
6148 representations of dst and src, respectively.
6152 if (GET_CODE (PATTERN (cui->insn)) != COND_EXEC)
6153 reverse_op (v->val_rtx, expr, cui->insn);
6155 mo.u.loc = loc;
6157 if (track_p)
6158 VAL_HOLDS_TRACK_EXPR (loc) = 1;
6159 if (preserve)
6161 VAL_NEEDS_RESOLUTION (loc) = resolve;
6162 preserve_value (v);
6164 if (mo.type == MO_CLOBBER)
6165 VAL_EXPR_IS_CLOBBERED (loc) = 1;
6166 if (mo.type == MO_COPY)
6167 VAL_EXPR_IS_COPIED (loc) = 1;
6169 mo.type = MO_VAL_SET;
6171 log_and_return:
6172 if (dump_file && (dump_flags & TDF_DETAILS))
6173 log_op_type (mo.u.loc, cui->bb, cui->insn, mo.type, dump_file);
6174 VTI (bb)->mos.safe_push (mo);
6177 /* Arguments to the call. */
6178 static rtx call_arguments;
6180 /* Compute call_arguments. */
6182 static void
6183 prepare_call_arguments (basic_block bb, rtx_insn *insn)
6185 rtx link, x, call;
6186 rtx prev, cur, next;
6187 rtx this_arg = NULL_RTX;
6188 tree type = NULL_TREE, t, fndecl = NULL_TREE;
6189 tree obj_type_ref = NULL_TREE;
6190 CUMULATIVE_ARGS args_so_far_v;
6191 cumulative_args_t args_so_far;
6193 memset (&args_so_far_v, 0, sizeof (args_so_far_v));
6194 args_so_far = pack_cumulative_args (&args_so_far_v);
6195 call = get_call_rtx_from (insn);
6196 if (call)
6198 if (GET_CODE (XEXP (XEXP (call, 0), 0)) == SYMBOL_REF)
6200 rtx symbol = XEXP (XEXP (call, 0), 0);
6201 if (SYMBOL_REF_DECL (symbol))
6202 fndecl = SYMBOL_REF_DECL (symbol);
6204 if (fndecl == NULL_TREE)
6205 fndecl = MEM_EXPR (XEXP (call, 0));
6206 if (fndecl
6207 && TREE_CODE (TREE_TYPE (fndecl)) != FUNCTION_TYPE
6208 && TREE_CODE (TREE_TYPE (fndecl)) != METHOD_TYPE)
6209 fndecl = NULL_TREE;
6210 if (fndecl && TYPE_ARG_TYPES (TREE_TYPE (fndecl)))
6211 type = TREE_TYPE (fndecl);
6212 if (fndecl && TREE_CODE (fndecl) != FUNCTION_DECL)
6214 if (TREE_CODE (fndecl) == INDIRECT_REF
6215 && TREE_CODE (TREE_OPERAND (fndecl, 0)) == OBJ_TYPE_REF)
6216 obj_type_ref = TREE_OPERAND (fndecl, 0);
6217 fndecl = NULL_TREE;
6219 if (type)
6221 for (t = TYPE_ARG_TYPES (type); t && t != void_list_node;
6222 t = TREE_CHAIN (t))
6223 if (TREE_CODE (TREE_VALUE (t)) == REFERENCE_TYPE
6224 && INTEGRAL_TYPE_P (TREE_TYPE (TREE_VALUE (t))))
6225 break;
6226 if ((t == NULL || t == void_list_node) && obj_type_ref == NULL_TREE)
6227 type = NULL;
6228 else
6230 int nargs ATTRIBUTE_UNUSED = list_length (TYPE_ARG_TYPES (type));
6231 link = CALL_INSN_FUNCTION_USAGE (insn);
6232 #ifndef PCC_STATIC_STRUCT_RETURN
6233 if (aggregate_value_p (TREE_TYPE (type), type)
6234 && targetm.calls.struct_value_rtx (type, 0) == 0)
6236 tree struct_addr = build_pointer_type (TREE_TYPE (type));
6237 machine_mode mode = TYPE_MODE (struct_addr);
6238 rtx reg;
6239 INIT_CUMULATIVE_ARGS (args_so_far_v, type, NULL_RTX, fndecl,
6240 nargs + 1);
6241 reg = targetm.calls.function_arg (args_so_far, mode,
6242 struct_addr, true);
6243 targetm.calls.function_arg_advance (args_so_far, mode,
6244 struct_addr, true);
6245 if (reg == NULL_RTX)
6247 for (; link; link = XEXP (link, 1))
6248 if (GET_CODE (XEXP (link, 0)) == USE
6249 && MEM_P (XEXP (XEXP (link, 0), 0)))
6251 link = XEXP (link, 1);
6252 break;
6256 else
6257 #endif
6258 INIT_CUMULATIVE_ARGS (args_so_far_v, type, NULL_RTX, fndecl,
6259 nargs);
6260 if (obj_type_ref && TYPE_ARG_TYPES (type) != void_list_node)
6262 machine_mode mode;
6263 t = TYPE_ARG_TYPES (type);
6264 mode = TYPE_MODE (TREE_VALUE (t));
6265 this_arg = targetm.calls.function_arg (args_so_far, mode,
6266 TREE_VALUE (t), true);
6267 if (this_arg && !REG_P (this_arg))
6268 this_arg = NULL_RTX;
6269 else if (this_arg == NULL_RTX)
6271 for (; link; link = XEXP (link, 1))
6272 if (GET_CODE (XEXP (link, 0)) == USE
6273 && MEM_P (XEXP (XEXP (link, 0), 0)))
6275 this_arg = XEXP (XEXP (link, 0), 0);
6276 break;
6283 t = type ? TYPE_ARG_TYPES (type) : NULL_TREE;
6285 for (link = CALL_INSN_FUNCTION_USAGE (insn); link; link = XEXP (link, 1))
6286 if (GET_CODE (XEXP (link, 0)) == USE)
6288 rtx item = NULL_RTX;
6289 x = XEXP (XEXP (link, 0), 0);
6290 if (GET_MODE (link) == VOIDmode
6291 || GET_MODE (link) == BLKmode
6292 || (GET_MODE (link) != GET_MODE (x)
6293 && ((GET_MODE_CLASS (GET_MODE (link)) != MODE_INT
6294 && GET_MODE_CLASS (GET_MODE (link)) != MODE_PARTIAL_INT)
6295 || (GET_MODE_CLASS (GET_MODE (x)) != MODE_INT
6296 && GET_MODE_CLASS (GET_MODE (x)) != MODE_PARTIAL_INT))))
6297 /* Can't do anything for these, if the original type mode
6298 isn't known or can't be converted. */;
6299 else if (REG_P (x))
6301 cselib_val *val = cselib_lookup (x, GET_MODE (x), 0, VOIDmode);
6302 if (val && cselib_preserved_value_p (val))
6303 item = val->val_rtx;
6304 else if (GET_MODE_CLASS (GET_MODE (x)) == MODE_INT
6305 || GET_MODE_CLASS (GET_MODE (x)) == MODE_PARTIAL_INT)
6307 machine_mode mode = GET_MODE (x);
6309 while ((mode = GET_MODE_WIDER_MODE (mode)) != VOIDmode
6310 && GET_MODE_BITSIZE (mode) <= BITS_PER_WORD)
6312 rtx reg = simplify_subreg (mode, x, GET_MODE (x), 0);
6314 if (reg == NULL_RTX || !REG_P (reg))
6315 continue;
6316 val = cselib_lookup (reg, mode, 0, VOIDmode);
6317 if (val && cselib_preserved_value_p (val))
6319 item = val->val_rtx;
6320 break;
6325 else if (MEM_P (x))
6327 rtx mem = x;
6328 cselib_val *val;
6330 if (!frame_pointer_needed)
6332 struct adjust_mem_data amd;
6333 amd.mem_mode = VOIDmode;
6334 amd.stack_adjust = -VTI (bb)->out.stack_adjust;
6335 amd.store = true;
6336 mem = simplify_replace_fn_rtx (mem, NULL_RTX, adjust_mems,
6337 &amd);
6338 gcc_assert (amd.side_effects.is_empty ());
6340 val = cselib_lookup (mem, GET_MODE (mem), 0, VOIDmode);
6341 if (val && cselib_preserved_value_p (val))
6342 item = val->val_rtx;
6343 else if (GET_MODE_CLASS (GET_MODE (mem)) != MODE_INT
6344 && GET_MODE_CLASS (GET_MODE (mem)) != MODE_PARTIAL_INT)
6346 /* For non-integer stack argument see also if they weren't
6347 initialized by integers. */
6348 machine_mode imode = int_mode_for_mode (GET_MODE (mem));
6349 if (imode != GET_MODE (mem) && imode != BLKmode)
6351 val = cselib_lookup (adjust_address_nv (mem, imode, 0),
6352 imode, 0, VOIDmode);
6353 if (val && cselib_preserved_value_p (val))
6354 item = lowpart_subreg (GET_MODE (x), val->val_rtx,
6355 imode);
6359 if (item)
6361 rtx x2 = x;
6362 if (GET_MODE (item) != GET_MODE (link))
6363 item = lowpart_subreg (GET_MODE (link), item, GET_MODE (item));
6364 if (GET_MODE (x2) != GET_MODE (link))
6365 x2 = lowpart_subreg (GET_MODE (link), x2, GET_MODE (x2));
6366 item = gen_rtx_CONCAT (GET_MODE (link), x2, item);
6367 call_arguments
6368 = gen_rtx_EXPR_LIST (VOIDmode, item, call_arguments);
6370 if (t && t != void_list_node)
6372 tree argtype = TREE_VALUE (t);
6373 machine_mode mode = TYPE_MODE (argtype);
6374 rtx reg;
6375 if (pass_by_reference (&args_so_far_v, mode, argtype, true))
6377 argtype = build_pointer_type (argtype);
6378 mode = TYPE_MODE (argtype);
6380 reg = targetm.calls.function_arg (args_so_far, mode,
6381 argtype, true);
6382 if (TREE_CODE (argtype) == REFERENCE_TYPE
6383 && INTEGRAL_TYPE_P (TREE_TYPE (argtype))
6384 && reg
6385 && REG_P (reg)
6386 && GET_MODE (reg) == mode
6387 && (GET_MODE_CLASS (mode) == MODE_INT
6388 || GET_MODE_CLASS (mode) == MODE_PARTIAL_INT)
6389 && REG_P (x)
6390 && REGNO (x) == REGNO (reg)
6391 && GET_MODE (x) == mode
6392 && item)
6394 machine_mode indmode
6395 = TYPE_MODE (TREE_TYPE (argtype));
6396 rtx mem = gen_rtx_MEM (indmode, x);
6397 cselib_val *val = cselib_lookup (mem, indmode, 0, VOIDmode);
6398 if (val && cselib_preserved_value_p (val))
6400 item = gen_rtx_CONCAT (indmode, mem, val->val_rtx);
6401 call_arguments = gen_rtx_EXPR_LIST (VOIDmode, item,
6402 call_arguments);
6404 else
6406 struct elt_loc_list *l;
6407 tree initial;
6409 /* Try harder, when passing address of a constant
6410 pool integer it can be easily read back. */
6411 item = XEXP (item, 1);
6412 if (GET_CODE (item) == SUBREG)
6413 item = SUBREG_REG (item);
6414 gcc_assert (GET_CODE (item) == VALUE);
6415 val = CSELIB_VAL_PTR (item);
6416 for (l = val->locs; l; l = l->next)
6417 if (GET_CODE (l->loc) == SYMBOL_REF
6418 && TREE_CONSTANT_POOL_ADDRESS_P (l->loc)
6419 && SYMBOL_REF_DECL (l->loc)
6420 && DECL_INITIAL (SYMBOL_REF_DECL (l->loc)))
6422 initial = DECL_INITIAL (SYMBOL_REF_DECL (l->loc));
6423 if (tree_fits_shwi_p (initial))
6425 item = GEN_INT (tree_to_shwi (initial));
6426 item = gen_rtx_CONCAT (indmode, mem, item);
6427 call_arguments
6428 = gen_rtx_EXPR_LIST (VOIDmode, item,
6429 call_arguments);
6431 break;
6435 targetm.calls.function_arg_advance (args_so_far, mode,
6436 argtype, true);
6437 t = TREE_CHAIN (t);
6441 /* Add debug arguments. */
6442 if (fndecl
6443 && TREE_CODE (fndecl) == FUNCTION_DECL
6444 && DECL_HAS_DEBUG_ARGS_P (fndecl))
6446 vec<tree, va_gc> **debug_args = decl_debug_args_lookup (fndecl);
6447 if (debug_args)
6449 unsigned int ix;
6450 tree param;
6451 for (ix = 0; vec_safe_iterate (*debug_args, ix, &param); ix += 2)
6453 rtx item;
6454 tree dtemp = (**debug_args)[ix + 1];
6455 machine_mode mode = DECL_MODE (dtemp);
6456 item = gen_rtx_DEBUG_PARAMETER_REF (mode, param);
6457 item = gen_rtx_CONCAT (mode, item, DECL_RTL_KNOWN_SET (dtemp));
6458 call_arguments = gen_rtx_EXPR_LIST (VOIDmode, item,
6459 call_arguments);
6464 /* Reverse call_arguments chain. */
6465 prev = NULL_RTX;
6466 for (cur = call_arguments; cur; cur = next)
6468 next = XEXP (cur, 1);
6469 XEXP (cur, 1) = prev;
6470 prev = cur;
6472 call_arguments = prev;
6474 x = get_call_rtx_from (insn);
6475 if (x)
6477 x = XEXP (XEXP (x, 0), 0);
6478 if (GET_CODE (x) == SYMBOL_REF)
6479 /* Don't record anything. */;
6480 else if (CONSTANT_P (x))
6482 x = gen_rtx_CONCAT (GET_MODE (x) == VOIDmode ? Pmode : GET_MODE (x),
6483 pc_rtx, x);
6484 call_arguments
6485 = gen_rtx_EXPR_LIST (VOIDmode, x, call_arguments);
6487 else
6489 cselib_val *val = cselib_lookup (x, GET_MODE (x), 0, VOIDmode);
6490 if (val && cselib_preserved_value_p (val))
6492 x = gen_rtx_CONCAT (GET_MODE (x), pc_rtx, val->val_rtx);
6493 call_arguments
6494 = gen_rtx_EXPR_LIST (VOIDmode, x, call_arguments);
6498 if (this_arg)
6500 machine_mode mode
6501 = TYPE_MODE (TREE_TYPE (OBJ_TYPE_REF_EXPR (obj_type_ref)));
6502 rtx clobbered = gen_rtx_MEM (mode, this_arg);
6503 HOST_WIDE_INT token
6504 = tree_to_shwi (OBJ_TYPE_REF_TOKEN (obj_type_ref));
6505 if (token)
6506 clobbered = plus_constant (mode, clobbered,
6507 token * GET_MODE_SIZE (mode));
6508 clobbered = gen_rtx_MEM (mode, clobbered);
6509 x = gen_rtx_CONCAT (mode, gen_rtx_CLOBBER (VOIDmode, pc_rtx), clobbered);
6510 call_arguments
6511 = gen_rtx_EXPR_LIST (VOIDmode, x, call_arguments);
6515 /* Callback for cselib_record_sets_hook, that records as micro
6516 operations uses and stores in an insn after cselib_record_sets has
6517 analyzed the sets in an insn, but before it modifies the stored
6518 values in the internal tables, unless cselib_record_sets doesn't
6519 call it directly (perhaps because we're not doing cselib in the
6520 first place, in which case sets and n_sets will be 0). */
6522 static void
6523 add_with_sets (rtx_insn *insn, struct cselib_set *sets, int n_sets)
6525 basic_block bb = BLOCK_FOR_INSN (insn);
6526 int n1, n2;
6527 struct count_use_info cui;
6528 micro_operation *mos;
6530 cselib_hook_called = true;
6532 cui.insn = insn;
6533 cui.bb = bb;
6534 cui.sets = sets;
6535 cui.n_sets = n_sets;
6537 n1 = VTI (bb)->mos.length ();
6538 cui.store_p = false;
6539 note_uses (&PATTERN (insn), add_uses_1, &cui);
6540 n2 = VTI (bb)->mos.length () - 1;
6541 mos = VTI (bb)->mos.address ();
6543 /* Order the MO_USEs to be before MO_USE_NO_VARs and MO_VAL_USE, and
6544 MO_VAL_LOC last. */
6545 while (n1 < n2)
6547 while (n1 < n2 && mos[n1].type == MO_USE)
6548 n1++;
6549 while (n1 < n2 && mos[n2].type != MO_USE)
6550 n2--;
6551 if (n1 < n2)
6552 std::swap (mos[n1], mos[n2]);
6555 n2 = VTI (bb)->mos.length () - 1;
6556 while (n1 < n2)
6558 while (n1 < n2 && mos[n1].type != MO_VAL_LOC)
6559 n1++;
6560 while (n1 < n2 && mos[n2].type == MO_VAL_LOC)
6561 n2--;
6562 if (n1 < n2)
6563 std::swap (mos[n1], mos[n2]);
6566 if (CALL_P (insn))
6568 micro_operation mo;
6570 mo.type = MO_CALL;
6571 mo.insn = insn;
6572 mo.u.loc = call_arguments;
6573 call_arguments = NULL_RTX;
6575 if (dump_file && (dump_flags & TDF_DETAILS))
6576 log_op_type (PATTERN (insn), bb, insn, mo.type, dump_file);
6577 VTI (bb)->mos.safe_push (mo);
6580 n1 = VTI (bb)->mos.length ();
6581 /* This will record NEXT_INSN (insn), such that we can
6582 insert notes before it without worrying about any
6583 notes that MO_USEs might emit after the insn. */
6584 cui.store_p = true;
6585 note_stores (PATTERN (insn), add_stores, &cui);
6586 n2 = VTI (bb)->mos.length () - 1;
6587 mos = VTI (bb)->mos.address ();
6589 /* Order the MO_VAL_USEs first (note_stores does nothing
6590 on DEBUG_INSNs, so there are no MO_VAL_LOCs from this
6591 insn), then MO_CLOBBERs, then MO_SET/MO_COPY/MO_VAL_SET. */
6592 while (n1 < n2)
6594 while (n1 < n2 && mos[n1].type == MO_VAL_USE)
6595 n1++;
6596 while (n1 < n2 && mos[n2].type != MO_VAL_USE)
6597 n2--;
6598 if (n1 < n2)
6599 std::swap (mos[n1], mos[n2]);
6602 n2 = VTI (bb)->mos.length () - 1;
6603 while (n1 < n2)
6605 while (n1 < n2 && mos[n1].type == MO_CLOBBER)
6606 n1++;
6607 while (n1 < n2 && mos[n2].type != MO_CLOBBER)
6608 n2--;
6609 if (n1 < n2)
6610 std::swap (mos[n1], mos[n2]);
6614 static enum var_init_status
6615 find_src_status (dataflow_set *in, rtx src)
6617 tree decl = NULL_TREE;
6618 enum var_init_status status = VAR_INIT_STATUS_UNINITIALIZED;
6620 if (! flag_var_tracking_uninit)
6621 status = VAR_INIT_STATUS_INITIALIZED;
6623 if (src && REG_P (src))
6624 decl = var_debug_decl (REG_EXPR (src));
6625 else if (src && MEM_P (src))
6626 decl = var_debug_decl (MEM_EXPR (src));
6628 if (src && decl)
6629 status = get_init_value (in, src, dv_from_decl (decl));
6631 return status;
6634 /* SRC is the source of an assignment. Use SET to try to find what
6635 was ultimately assigned to SRC. Return that value if known,
6636 otherwise return SRC itself. */
6638 static rtx
6639 find_src_set_src (dataflow_set *set, rtx src)
6641 tree decl = NULL_TREE; /* The variable being copied around. */
6642 rtx set_src = NULL_RTX; /* The value for "decl" stored in "src". */
6643 variable *var;
6644 location_chain *nextp;
6645 int i;
6646 bool found;
6648 if (src && REG_P (src))
6649 decl = var_debug_decl (REG_EXPR (src));
6650 else if (src && MEM_P (src))
6651 decl = var_debug_decl (MEM_EXPR (src));
6653 if (src && decl)
6655 decl_or_value dv = dv_from_decl (decl);
6657 var = shared_hash_find (set->vars, dv);
6658 if (var)
6660 found = false;
6661 for (i = 0; i < var->n_var_parts && !found; i++)
6662 for (nextp = var->var_part[i].loc_chain; nextp && !found;
6663 nextp = nextp->next)
6664 if (rtx_equal_p (nextp->loc, src))
6666 set_src = nextp->set_src;
6667 found = true;
6673 return set_src;
6676 /* Compute the changes of variable locations in the basic block BB. */
6678 static bool
6679 compute_bb_dataflow (basic_block bb)
6681 unsigned int i;
6682 micro_operation *mo;
6683 bool changed;
6684 dataflow_set old_out;
6685 dataflow_set *in = &VTI (bb)->in;
6686 dataflow_set *out = &VTI (bb)->out;
6688 dataflow_set_init (&old_out);
6689 dataflow_set_copy (&old_out, out);
6690 dataflow_set_copy (out, in);
6692 if (MAY_HAVE_DEBUG_INSNS)
6693 local_get_addr_cache = new hash_map<rtx, rtx>;
6695 FOR_EACH_VEC_ELT (VTI (bb)->mos, i, mo)
6697 rtx_insn *insn = mo->insn;
6699 switch (mo->type)
6701 case MO_CALL:
6702 dataflow_set_clear_at_call (out, insn);
6703 break;
6705 case MO_USE:
6707 rtx loc = mo->u.loc;
6709 if (REG_P (loc))
6710 var_reg_set (out, loc, VAR_INIT_STATUS_UNINITIALIZED, NULL);
6711 else if (MEM_P (loc))
6712 var_mem_set (out, loc, VAR_INIT_STATUS_UNINITIALIZED, NULL);
6714 break;
6716 case MO_VAL_LOC:
6718 rtx loc = mo->u.loc;
6719 rtx val, vloc;
6720 tree var;
6722 if (GET_CODE (loc) == CONCAT)
6724 val = XEXP (loc, 0);
6725 vloc = XEXP (loc, 1);
6727 else
6729 val = NULL_RTX;
6730 vloc = loc;
6733 var = PAT_VAR_LOCATION_DECL (vloc);
6735 clobber_variable_part (out, NULL_RTX,
6736 dv_from_decl (var), 0, NULL_RTX);
6737 if (val)
6739 if (VAL_NEEDS_RESOLUTION (loc))
6740 val_resolve (out, val, PAT_VAR_LOCATION_LOC (vloc), insn);
6741 set_variable_part (out, val, dv_from_decl (var), 0,
6742 VAR_INIT_STATUS_INITIALIZED, NULL_RTX,
6743 INSERT);
6745 else if (!VAR_LOC_UNKNOWN_P (PAT_VAR_LOCATION_LOC (vloc)))
6746 set_variable_part (out, PAT_VAR_LOCATION_LOC (vloc),
6747 dv_from_decl (var), 0,
6748 VAR_INIT_STATUS_INITIALIZED, NULL_RTX,
6749 INSERT);
6751 break;
6753 case MO_VAL_USE:
6755 rtx loc = mo->u.loc;
6756 rtx val, vloc, uloc;
6758 vloc = uloc = XEXP (loc, 1);
6759 val = XEXP (loc, 0);
6761 if (GET_CODE (val) == CONCAT)
6763 uloc = XEXP (val, 1);
6764 val = XEXP (val, 0);
6767 if (VAL_NEEDS_RESOLUTION (loc))
6768 val_resolve (out, val, vloc, insn);
6769 else
6770 val_store (out, val, uloc, insn, false);
6772 if (VAL_HOLDS_TRACK_EXPR (loc))
6774 if (GET_CODE (uloc) == REG)
6775 var_reg_set (out, uloc, VAR_INIT_STATUS_UNINITIALIZED,
6776 NULL);
6777 else if (GET_CODE (uloc) == MEM)
6778 var_mem_set (out, uloc, VAR_INIT_STATUS_UNINITIALIZED,
6779 NULL);
6782 break;
6784 case MO_VAL_SET:
6786 rtx loc = mo->u.loc;
6787 rtx val, vloc, uloc;
6788 rtx dstv, srcv;
6790 vloc = loc;
6791 uloc = XEXP (vloc, 1);
6792 val = XEXP (vloc, 0);
6793 vloc = uloc;
6795 if (GET_CODE (uloc) == SET)
6797 dstv = SET_DEST (uloc);
6798 srcv = SET_SRC (uloc);
6800 else
6802 dstv = uloc;
6803 srcv = NULL;
6806 if (GET_CODE (val) == CONCAT)
6808 dstv = vloc = XEXP (val, 1);
6809 val = XEXP (val, 0);
6812 if (GET_CODE (vloc) == SET)
6814 srcv = SET_SRC (vloc);
6816 gcc_assert (val != srcv);
6817 gcc_assert (vloc == uloc || VAL_NEEDS_RESOLUTION (loc));
6819 dstv = vloc = SET_DEST (vloc);
6821 if (VAL_NEEDS_RESOLUTION (loc))
6822 val_resolve (out, val, srcv, insn);
6824 else if (VAL_NEEDS_RESOLUTION (loc))
6826 gcc_assert (GET_CODE (uloc) == SET
6827 && GET_CODE (SET_SRC (uloc)) == REG);
6828 val_resolve (out, val, SET_SRC (uloc), insn);
6831 if (VAL_HOLDS_TRACK_EXPR (loc))
6833 if (VAL_EXPR_IS_CLOBBERED (loc))
6835 if (REG_P (uloc))
6836 var_reg_delete (out, uloc, true);
6837 else if (MEM_P (uloc))
6839 gcc_assert (MEM_P (dstv));
6840 gcc_assert (MEM_ATTRS (dstv) == MEM_ATTRS (uloc));
6841 var_mem_delete (out, dstv, true);
6844 else
6846 bool copied_p = VAL_EXPR_IS_COPIED (loc);
6847 rtx src = NULL, dst = uloc;
6848 enum var_init_status status = VAR_INIT_STATUS_INITIALIZED;
6850 if (GET_CODE (uloc) == SET)
6852 src = SET_SRC (uloc);
6853 dst = SET_DEST (uloc);
6856 if (copied_p)
6858 if (flag_var_tracking_uninit)
6860 status = find_src_status (in, src);
6862 if (status == VAR_INIT_STATUS_UNKNOWN)
6863 status = find_src_status (out, src);
6866 src = find_src_set_src (in, src);
6869 if (REG_P (dst))
6870 var_reg_delete_and_set (out, dst, !copied_p,
6871 status, srcv);
6872 else if (MEM_P (dst))
6874 gcc_assert (MEM_P (dstv));
6875 gcc_assert (MEM_ATTRS (dstv) == MEM_ATTRS (dst));
6876 var_mem_delete_and_set (out, dstv, !copied_p,
6877 status, srcv);
6881 else if (REG_P (uloc))
6882 var_regno_delete (out, REGNO (uloc));
6883 else if (MEM_P (uloc))
6885 gcc_checking_assert (GET_CODE (vloc) == MEM);
6886 gcc_checking_assert (dstv == vloc);
6887 if (dstv != vloc)
6888 clobber_overlapping_mems (out, vloc);
6891 val_store (out, val, dstv, insn, true);
6893 break;
6895 case MO_SET:
6897 rtx loc = mo->u.loc;
6898 rtx set_src = NULL;
6900 if (GET_CODE (loc) == SET)
6902 set_src = SET_SRC (loc);
6903 loc = SET_DEST (loc);
6906 if (REG_P (loc))
6907 var_reg_delete_and_set (out, loc, true, VAR_INIT_STATUS_INITIALIZED,
6908 set_src);
6909 else if (MEM_P (loc))
6910 var_mem_delete_and_set (out, loc, true, VAR_INIT_STATUS_INITIALIZED,
6911 set_src);
6913 break;
6915 case MO_COPY:
6917 rtx loc = mo->u.loc;
6918 enum var_init_status src_status;
6919 rtx set_src = NULL;
6921 if (GET_CODE (loc) == SET)
6923 set_src = SET_SRC (loc);
6924 loc = SET_DEST (loc);
6927 if (! flag_var_tracking_uninit)
6928 src_status = VAR_INIT_STATUS_INITIALIZED;
6929 else
6931 src_status = find_src_status (in, set_src);
6933 if (src_status == VAR_INIT_STATUS_UNKNOWN)
6934 src_status = find_src_status (out, set_src);
6937 set_src = find_src_set_src (in, set_src);
6939 if (REG_P (loc))
6940 var_reg_delete_and_set (out, loc, false, src_status, set_src);
6941 else if (MEM_P (loc))
6942 var_mem_delete_and_set (out, loc, false, src_status, set_src);
6944 break;
6946 case MO_USE_NO_VAR:
6948 rtx loc = mo->u.loc;
6950 if (REG_P (loc))
6951 var_reg_delete (out, loc, false);
6952 else if (MEM_P (loc))
6953 var_mem_delete (out, loc, false);
6955 break;
6957 case MO_CLOBBER:
6959 rtx loc = mo->u.loc;
6961 if (REG_P (loc))
6962 var_reg_delete (out, loc, true);
6963 else if (MEM_P (loc))
6964 var_mem_delete (out, loc, true);
6966 break;
6968 case MO_ADJUST:
6969 out->stack_adjust += mo->u.adjust;
6970 break;
6974 if (MAY_HAVE_DEBUG_INSNS)
6976 delete local_get_addr_cache;
6977 local_get_addr_cache = NULL;
6979 dataflow_set_equiv_regs (out);
6980 shared_hash_htab (out->vars)
6981 ->traverse <dataflow_set *, canonicalize_values_mark> (out);
6982 shared_hash_htab (out->vars)
6983 ->traverse <dataflow_set *, canonicalize_values_star> (out);
6984 if (flag_checking)
6985 shared_hash_htab (out->vars)
6986 ->traverse <dataflow_set *, canonicalize_loc_order_check> (out);
6988 changed = dataflow_set_different (&old_out, out);
6989 dataflow_set_destroy (&old_out);
6990 return changed;
6993 /* Find the locations of variables in the whole function. */
6995 static bool
6996 vt_find_locations (void)
6998 bb_heap_t *worklist = new bb_heap_t (LONG_MIN);
6999 bb_heap_t *pending = new bb_heap_t (LONG_MIN);
7000 sbitmap in_worklist, in_pending;
7001 basic_block bb;
7002 edge e;
7003 int *bb_order;
7004 int *rc_order;
7005 int i;
7006 int htabsz = 0;
7007 int htabmax = PARAM_VALUE (PARAM_MAX_VARTRACK_SIZE);
7008 bool success = true;
7010 timevar_push (TV_VAR_TRACKING_DATAFLOW);
7011 /* Compute reverse completion order of depth first search of the CFG
7012 so that the data-flow runs faster. */
7013 rc_order = XNEWVEC (int, n_basic_blocks_for_fn (cfun) - NUM_FIXED_BLOCKS);
7014 bb_order = XNEWVEC (int, last_basic_block_for_fn (cfun));
7015 pre_and_rev_post_order_compute (NULL, rc_order, false);
7016 for (i = 0; i < n_basic_blocks_for_fn (cfun) - NUM_FIXED_BLOCKS; i++)
7017 bb_order[rc_order[i]] = i;
7018 free (rc_order);
7020 auto_sbitmap visited (last_basic_block_for_fn (cfun));
7021 in_worklist = sbitmap_alloc (last_basic_block_for_fn (cfun));
7022 in_pending = sbitmap_alloc (last_basic_block_for_fn (cfun));
7023 bitmap_clear (in_worklist);
7025 FOR_EACH_BB_FN (bb, cfun)
7026 pending->insert (bb_order[bb->index], bb);
7027 bitmap_ones (in_pending);
7029 while (success && !pending->empty ())
7031 std::swap (worklist, pending);
7032 std::swap (in_worklist, in_pending);
7034 bitmap_clear (visited);
7036 while (!worklist->empty ())
7038 bb = worklist->extract_min ();
7039 bitmap_clear_bit (in_worklist, bb->index);
7040 gcc_assert (!bitmap_bit_p (visited, bb->index));
7041 if (!bitmap_bit_p (visited, bb->index))
7043 bool changed;
7044 edge_iterator ei;
7045 int oldinsz, oldoutsz;
7047 bitmap_set_bit (visited, bb->index);
7049 if (VTI (bb)->in.vars)
7051 htabsz
7052 -= shared_hash_htab (VTI (bb)->in.vars)->size ()
7053 + shared_hash_htab (VTI (bb)->out.vars)->size ();
7054 oldinsz = shared_hash_htab (VTI (bb)->in.vars)->elements ();
7055 oldoutsz
7056 = shared_hash_htab (VTI (bb)->out.vars)->elements ();
7058 else
7059 oldinsz = oldoutsz = 0;
7061 if (MAY_HAVE_DEBUG_INSNS)
7063 dataflow_set *in = &VTI (bb)->in, *first_out = NULL;
7064 bool first = true, adjust = false;
7066 /* Calculate the IN set as the intersection of
7067 predecessor OUT sets. */
7069 dataflow_set_clear (in);
7070 dst_can_be_shared = true;
7072 FOR_EACH_EDGE (e, ei, bb->preds)
7073 if (!VTI (e->src)->flooded)
7074 gcc_assert (bb_order[bb->index]
7075 <= bb_order[e->src->index]);
7076 else if (first)
7078 dataflow_set_copy (in, &VTI (e->src)->out);
7079 first_out = &VTI (e->src)->out;
7080 first = false;
7082 else
7084 dataflow_set_merge (in, &VTI (e->src)->out);
7085 adjust = true;
7088 if (adjust)
7090 dataflow_post_merge_adjust (in, &VTI (bb)->permp);
7092 if (flag_checking)
7093 /* Merge and merge_adjust should keep entries in
7094 canonical order. */
7095 shared_hash_htab (in->vars)
7096 ->traverse <dataflow_set *,
7097 canonicalize_loc_order_check> (in);
7099 if (dst_can_be_shared)
7101 shared_hash_destroy (in->vars);
7102 in->vars = shared_hash_copy (first_out->vars);
7106 VTI (bb)->flooded = true;
7108 else
7110 /* Calculate the IN set as union of predecessor OUT sets. */
7111 dataflow_set_clear (&VTI (bb)->in);
7112 FOR_EACH_EDGE (e, ei, bb->preds)
7113 dataflow_set_union (&VTI (bb)->in, &VTI (e->src)->out);
7116 changed = compute_bb_dataflow (bb);
7117 htabsz += shared_hash_htab (VTI (bb)->in.vars)->size ()
7118 + shared_hash_htab (VTI (bb)->out.vars)->size ();
7120 if (htabmax && htabsz > htabmax)
7122 if (MAY_HAVE_DEBUG_INSNS)
7123 inform (DECL_SOURCE_LOCATION (cfun->decl),
7124 "variable tracking size limit exceeded with "
7125 "-fvar-tracking-assignments, retrying without");
7126 else
7127 inform (DECL_SOURCE_LOCATION (cfun->decl),
7128 "variable tracking size limit exceeded");
7129 success = false;
7130 break;
7133 if (changed)
7135 FOR_EACH_EDGE (e, ei, bb->succs)
7137 if (e->dest == EXIT_BLOCK_PTR_FOR_FN (cfun))
7138 continue;
7140 if (bitmap_bit_p (visited, e->dest->index))
7142 if (!bitmap_bit_p (in_pending, e->dest->index))
7144 /* Send E->DEST to next round. */
7145 bitmap_set_bit (in_pending, e->dest->index);
7146 pending->insert (bb_order[e->dest->index],
7147 e->dest);
7150 else if (!bitmap_bit_p (in_worklist, e->dest->index))
7152 /* Add E->DEST to current round. */
7153 bitmap_set_bit (in_worklist, e->dest->index);
7154 worklist->insert (bb_order[e->dest->index],
7155 e->dest);
7160 if (dump_file)
7161 fprintf (dump_file,
7162 "BB %i: in %i (was %i), out %i (was %i), rem %i + %i, tsz %i\n",
7163 bb->index,
7164 (int)shared_hash_htab (VTI (bb)->in.vars)->size (),
7165 oldinsz,
7166 (int)shared_hash_htab (VTI (bb)->out.vars)->size (),
7167 oldoutsz,
7168 (int)worklist->nodes (), (int)pending->nodes (),
7169 htabsz);
7171 if (dump_file && (dump_flags & TDF_DETAILS))
7173 fprintf (dump_file, "BB %i IN:\n", bb->index);
7174 dump_dataflow_set (&VTI (bb)->in);
7175 fprintf (dump_file, "BB %i OUT:\n", bb->index);
7176 dump_dataflow_set (&VTI (bb)->out);
7182 if (success && MAY_HAVE_DEBUG_INSNS)
7183 FOR_EACH_BB_FN (bb, cfun)
7184 gcc_assert (VTI (bb)->flooded);
7186 free (bb_order);
7187 delete worklist;
7188 delete pending;
7189 sbitmap_free (in_worklist);
7190 sbitmap_free (in_pending);
7192 timevar_pop (TV_VAR_TRACKING_DATAFLOW);
7193 return success;
7196 /* Print the content of the LIST to dump file. */
7198 static void
7199 dump_attrs_list (attrs *list)
7201 for (; list; list = list->next)
7203 if (dv_is_decl_p (list->dv))
7204 print_mem_expr (dump_file, dv_as_decl (list->dv));
7205 else
7206 print_rtl_single (dump_file, dv_as_value (list->dv));
7207 fprintf (dump_file, "+" HOST_WIDE_INT_PRINT_DEC, list->offset);
7209 fprintf (dump_file, "\n");
7212 /* Print the information about variable *SLOT to dump file. */
7215 dump_var_tracking_slot (variable **slot, void *data ATTRIBUTE_UNUSED)
7217 variable *var = *slot;
7219 dump_var (var);
7221 /* Continue traversing the hash table. */
7222 return 1;
7225 /* Print the information about variable VAR to dump file. */
7227 static void
7228 dump_var (variable *var)
7230 int i;
7231 location_chain *node;
7233 if (dv_is_decl_p (var->dv))
7235 const_tree decl = dv_as_decl (var->dv);
7237 if (DECL_NAME (decl))
7239 fprintf (dump_file, " name: %s",
7240 IDENTIFIER_POINTER (DECL_NAME (decl)));
7241 if (dump_flags & TDF_UID)
7242 fprintf (dump_file, "D.%u", DECL_UID (decl));
7244 else if (TREE_CODE (decl) == DEBUG_EXPR_DECL)
7245 fprintf (dump_file, " name: D#%u", DEBUG_TEMP_UID (decl));
7246 else
7247 fprintf (dump_file, " name: D.%u", DECL_UID (decl));
7248 fprintf (dump_file, "\n");
7250 else
7252 fputc (' ', dump_file);
7253 print_rtl_single (dump_file, dv_as_value (var->dv));
7256 for (i = 0; i < var->n_var_parts; i++)
7258 fprintf (dump_file, " offset %ld\n",
7259 (long)(var->onepart ? 0 : VAR_PART_OFFSET (var, i)));
7260 for (node = var->var_part[i].loc_chain; node; node = node->next)
7262 fprintf (dump_file, " ");
7263 if (node->init == VAR_INIT_STATUS_UNINITIALIZED)
7264 fprintf (dump_file, "[uninit]");
7265 print_rtl_single (dump_file, node->loc);
7270 /* Print the information about variables from hash table VARS to dump file. */
7272 static void
7273 dump_vars (variable_table_type *vars)
7275 if (vars->elements () > 0)
7277 fprintf (dump_file, "Variables:\n");
7278 vars->traverse <void *, dump_var_tracking_slot> (NULL);
7282 /* Print the dataflow set SET to dump file. */
7284 static void
7285 dump_dataflow_set (dataflow_set *set)
7287 int i;
7289 fprintf (dump_file, "Stack adjustment: " HOST_WIDE_INT_PRINT_DEC "\n",
7290 set->stack_adjust);
7291 for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
7293 if (set->regs[i])
7295 fprintf (dump_file, "Reg %d:", i);
7296 dump_attrs_list (set->regs[i]);
7299 dump_vars (shared_hash_htab (set->vars));
7300 fprintf (dump_file, "\n");
7303 /* Print the IN and OUT sets for each basic block to dump file. */
7305 static void
7306 dump_dataflow_sets (void)
7308 basic_block bb;
7310 FOR_EACH_BB_FN (bb, cfun)
7312 fprintf (dump_file, "\nBasic block %d:\n", bb->index);
7313 fprintf (dump_file, "IN:\n");
7314 dump_dataflow_set (&VTI (bb)->in);
7315 fprintf (dump_file, "OUT:\n");
7316 dump_dataflow_set (&VTI (bb)->out);
7320 /* Return the variable for DV in dropped_values, inserting one if
7321 requested with INSERT. */
7323 static inline variable *
7324 variable_from_dropped (decl_or_value dv, enum insert_option insert)
7326 variable **slot;
7327 variable *empty_var;
7328 onepart_enum onepart;
7330 slot = dropped_values->find_slot_with_hash (dv, dv_htab_hash (dv), insert);
7332 if (!slot)
7333 return NULL;
7335 if (*slot)
7336 return *slot;
7338 gcc_checking_assert (insert == INSERT);
7340 onepart = dv_onepart_p (dv);
7342 gcc_checking_assert (onepart == ONEPART_VALUE || onepart == ONEPART_DEXPR);
7344 empty_var = onepart_pool_allocate (onepart);
7345 empty_var->dv = dv;
7346 empty_var->refcount = 1;
7347 empty_var->n_var_parts = 0;
7348 empty_var->onepart = onepart;
7349 empty_var->in_changed_variables = false;
7350 empty_var->var_part[0].loc_chain = NULL;
7351 empty_var->var_part[0].cur_loc = NULL;
7352 VAR_LOC_1PAUX (empty_var) = NULL;
7353 set_dv_changed (dv, true);
7355 *slot = empty_var;
7357 return empty_var;
7360 /* Recover the one-part aux from dropped_values. */
7362 static struct onepart_aux *
7363 recover_dropped_1paux (variable *var)
7365 variable *dvar;
7367 gcc_checking_assert (var->onepart);
7369 if (VAR_LOC_1PAUX (var))
7370 return VAR_LOC_1PAUX (var);
7372 if (var->onepart == ONEPART_VDECL)
7373 return NULL;
7375 dvar = variable_from_dropped (var->dv, NO_INSERT);
7377 if (!dvar)
7378 return NULL;
7380 VAR_LOC_1PAUX (var) = VAR_LOC_1PAUX (dvar);
7381 VAR_LOC_1PAUX (dvar) = NULL;
7383 return VAR_LOC_1PAUX (var);
7386 /* Add variable VAR to the hash table of changed variables and
7387 if it has no locations delete it from SET's hash table. */
7389 static void
7390 variable_was_changed (variable *var, dataflow_set *set)
7392 hashval_t hash = dv_htab_hash (var->dv);
7394 if (emit_notes)
7396 variable **slot;
7398 /* Remember this decl or VALUE has been added to changed_variables. */
7399 set_dv_changed (var->dv, true);
7401 slot = changed_variables->find_slot_with_hash (var->dv, hash, INSERT);
7403 if (*slot)
7405 variable *old_var = *slot;
7406 gcc_assert (old_var->in_changed_variables);
7407 old_var->in_changed_variables = false;
7408 if (var != old_var && var->onepart)
7410 /* Restore the auxiliary info from an empty variable
7411 previously created for changed_variables, so it is
7412 not lost. */
7413 gcc_checking_assert (!VAR_LOC_1PAUX (var));
7414 VAR_LOC_1PAUX (var) = VAR_LOC_1PAUX (old_var);
7415 VAR_LOC_1PAUX (old_var) = NULL;
7417 variable_htab_free (*slot);
7420 if (set && var->n_var_parts == 0)
7422 onepart_enum onepart = var->onepart;
7423 variable *empty_var = NULL;
7424 variable **dslot = NULL;
7426 if (onepart == ONEPART_VALUE || onepart == ONEPART_DEXPR)
7428 dslot = dropped_values->find_slot_with_hash (var->dv,
7429 dv_htab_hash (var->dv),
7430 INSERT);
7431 empty_var = *dslot;
7433 if (empty_var)
7435 gcc_checking_assert (!empty_var->in_changed_variables);
7436 if (!VAR_LOC_1PAUX (var))
7438 VAR_LOC_1PAUX (var) = VAR_LOC_1PAUX (empty_var);
7439 VAR_LOC_1PAUX (empty_var) = NULL;
7441 else
7442 gcc_checking_assert (!VAR_LOC_1PAUX (empty_var));
7446 if (!empty_var)
7448 empty_var = onepart_pool_allocate (onepart);
7449 empty_var->dv = var->dv;
7450 empty_var->refcount = 1;
7451 empty_var->n_var_parts = 0;
7452 empty_var->onepart = onepart;
7453 if (dslot)
7455 empty_var->refcount++;
7456 *dslot = empty_var;
7459 else
7460 empty_var->refcount++;
7461 empty_var->in_changed_variables = true;
7462 *slot = empty_var;
7463 if (onepart)
7465 empty_var->var_part[0].loc_chain = NULL;
7466 empty_var->var_part[0].cur_loc = NULL;
7467 VAR_LOC_1PAUX (empty_var) = VAR_LOC_1PAUX (var);
7468 VAR_LOC_1PAUX (var) = NULL;
7470 goto drop_var;
7472 else
7474 if (var->onepart && !VAR_LOC_1PAUX (var))
7475 recover_dropped_1paux (var);
7476 var->refcount++;
7477 var->in_changed_variables = true;
7478 *slot = var;
7481 else
7483 gcc_assert (set);
7484 if (var->n_var_parts == 0)
7486 variable **slot;
7488 drop_var:
7489 slot = shared_hash_find_slot_noinsert (set->vars, var->dv);
7490 if (slot)
7492 if (shared_hash_shared (set->vars))
7493 slot = shared_hash_find_slot_unshare (&set->vars, var->dv,
7494 NO_INSERT);
7495 shared_hash_htab (set->vars)->clear_slot (slot);
7501 /* Look for the index in VAR->var_part corresponding to OFFSET.
7502 Return -1 if not found. If INSERTION_POINT is non-NULL, the
7503 referenced int will be set to the index that the part has or should
7504 have, if it should be inserted. */
7506 static inline int
7507 find_variable_location_part (variable *var, HOST_WIDE_INT offset,
7508 int *insertion_point)
7510 int pos, low, high;
7512 if (var->onepart)
7514 if (offset != 0)
7515 return -1;
7517 if (insertion_point)
7518 *insertion_point = 0;
7520 return var->n_var_parts - 1;
7523 /* Find the location part. */
7524 low = 0;
7525 high = var->n_var_parts;
7526 while (low != high)
7528 pos = (low + high) / 2;
7529 if (VAR_PART_OFFSET (var, pos) < offset)
7530 low = pos + 1;
7531 else
7532 high = pos;
7534 pos = low;
7536 if (insertion_point)
7537 *insertion_point = pos;
7539 if (pos < var->n_var_parts && VAR_PART_OFFSET (var, pos) == offset)
7540 return pos;
7542 return -1;
7545 static variable **
7546 set_slot_part (dataflow_set *set, rtx loc, variable **slot,
7547 decl_or_value dv, HOST_WIDE_INT offset,
7548 enum var_init_status initialized, rtx set_src)
7550 int pos;
7551 location_chain *node, *next;
7552 location_chain **nextp;
7553 variable *var;
7554 onepart_enum onepart;
7556 var = *slot;
7558 if (var)
7559 onepart = var->onepart;
7560 else
7561 onepart = dv_onepart_p (dv);
7563 gcc_checking_assert (offset == 0 || !onepart);
7564 gcc_checking_assert (loc != dv_as_opaque (dv));
7566 if (! flag_var_tracking_uninit)
7567 initialized = VAR_INIT_STATUS_INITIALIZED;
7569 if (!var)
7571 /* Create new variable information. */
7572 var = onepart_pool_allocate (onepart);
7573 var->dv = dv;
7574 var->refcount = 1;
7575 var->n_var_parts = 1;
7576 var->onepart = onepart;
7577 var->in_changed_variables = false;
7578 if (var->onepart)
7579 VAR_LOC_1PAUX (var) = NULL;
7580 else
7581 VAR_PART_OFFSET (var, 0) = offset;
7582 var->var_part[0].loc_chain = NULL;
7583 var->var_part[0].cur_loc = NULL;
7584 *slot = var;
7585 pos = 0;
7586 nextp = &var->var_part[0].loc_chain;
7588 else if (onepart)
7590 int r = -1, c = 0;
7592 gcc_assert (dv_as_opaque (var->dv) == dv_as_opaque (dv));
7594 pos = 0;
7596 if (GET_CODE (loc) == VALUE)
7598 for (nextp = &var->var_part[0].loc_chain; (node = *nextp);
7599 nextp = &node->next)
7600 if (GET_CODE (node->loc) == VALUE)
7602 if (node->loc == loc)
7604 r = 0;
7605 break;
7607 if (canon_value_cmp (node->loc, loc))
7608 c++;
7609 else
7611 r = 1;
7612 break;
7615 else if (REG_P (node->loc) || MEM_P (node->loc))
7616 c++;
7617 else
7619 r = 1;
7620 break;
7623 else if (REG_P (loc))
7625 for (nextp = &var->var_part[0].loc_chain; (node = *nextp);
7626 nextp = &node->next)
7627 if (REG_P (node->loc))
7629 if (REGNO (node->loc) < REGNO (loc))
7630 c++;
7631 else
7633 if (REGNO (node->loc) == REGNO (loc))
7634 r = 0;
7635 else
7636 r = 1;
7637 break;
7640 else
7642 r = 1;
7643 break;
7646 else if (MEM_P (loc))
7648 for (nextp = &var->var_part[0].loc_chain; (node = *nextp);
7649 nextp = &node->next)
7650 if (REG_P (node->loc))
7651 c++;
7652 else if (MEM_P (node->loc))
7654 if ((r = loc_cmp (XEXP (node->loc, 0), XEXP (loc, 0))) >= 0)
7655 break;
7656 else
7657 c++;
7659 else
7661 r = 1;
7662 break;
7665 else
7666 for (nextp = &var->var_part[0].loc_chain; (node = *nextp);
7667 nextp = &node->next)
7668 if ((r = loc_cmp (node->loc, loc)) >= 0)
7669 break;
7670 else
7671 c++;
7673 if (r == 0)
7674 return slot;
7676 if (shared_var_p (var, set->vars))
7678 slot = unshare_variable (set, slot, var, initialized);
7679 var = *slot;
7680 for (nextp = &var->var_part[0].loc_chain; c;
7681 nextp = &(*nextp)->next)
7682 c--;
7683 gcc_assert ((!node && !*nextp) || node->loc == (*nextp)->loc);
7686 else
7688 int inspos = 0;
7690 gcc_assert (dv_as_decl (var->dv) == dv_as_decl (dv));
7692 pos = find_variable_location_part (var, offset, &inspos);
7694 if (pos >= 0)
7696 node = var->var_part[pos].loc_chain;
7698 if (node
7699 && ((REG_P (node->loc) && REG_P (loc)
7700 && REGNO (node->loc) == REGNO (loc))
7701 || rtx_equal_p (node->loc, loc)))
7703 /* LOC is in the beginning of the chain so we have nothing
7704 to do. */
7705 if (node->init < initialized)
7706 node->init = initialized;
7707 if (set_src != NULL)
7708 node->set_src = set_src;
7710 return slot;
7712 else
7714 /* We have to make a copy of a shared variable. */
7715 if (shared_var_p (var, set->vars))
7717 slot = unshare_variable (set, slot, var, initialized);
7718 var = *slot;
7722 else
7724 /* We have not found the location part, new one will be created. */
7726 /* We have to make a copy of the shared variable. */
7727 if (shared_var_p (var, set->vars))
7729 slot = unshare_variable (set, slot, var, initialized);
7730 var = *slot;
7733 /* We track only variables whose size is <= MAX_VAR_PARTS bytes
7734 thus there are at most MAX_VAR_PARTS different offsets. */
7735 gcc_assert (var->n_var_parts < MAX_VAR_PARTS
7736 && (!var->n_var_parts || !onepart));
7738 /* We have to move the elements of array starting at index
7739 inspos to the next position. */
7740 for (pos = var->n_var_parts; pos > inspos; pos--)
7741 var->var_part[pos] = var->var_part[pos - 1];
7743 var->n_var_parts++;
7744 gcc_checking_assert (!onepart);
7745 VAR_PART_OFFSET (var, pos) = offset;
7746 var->var_part[pos].loc_chain = NULL;
7747 var->var_part[pos].cur_loc = NULL;
7750 /* Delete the location from the list. */
7751 nextp = &var->var_part[pos].loc_chain;
7752 for (node = var->var_part[pos].loc_chain; node; node = next)
7754 next = node->next;
7755 if ((REG_P (node->loc) && REG_P (loc)
7756 && REGNO (node->loc) == REGNO (loc))
7757 || rtx_equal_p (node->loc, loc))
7759 /* Save these values, to assign to the new node, before
7760 deleting this one. */
7761 if (node->init > initialized)
7762 initialized = node->init;
7763 if (node->set_src != NULL && set_src == NULL)
7764 set_src = node->set_src;
7765 if (var->var_part[pos].cur_loc == node->loc)
7766 var->var_part[pos].cur_loc = NULL;
7767 delete node;
7768 *nextp = next;
7769 break;
7771 else
7772 nextp = &node->next;
7775 nextp = &var->var_part[pos].loc_chain;
7778 /* Add the location to the beginning. */
7779 node = new location_chain;
7780 node->loc = loc;
7781 node->init = initialized;
7782 node->set_src = set_src;
7783 node->next = *nextp;
7784 *nextp = node;
7786 /* If no location was emitted do so. */
7787 if (var->var_part[pos].cur_loc == NULL)
7788 variable_was_changed (var, set);
7790 return slot;
7793 /* Set the part of variable's location in the dataflow set SET. The
7794 variable part is specified by variable's declaration in DV and
7795 offset OFFSET and the part's location by LOC. IOPT should be
7796 NO_INSERT if the variable is known to be in SET already and the
7797 variable hash table must not be resized, and INSERT otherwise. */
7799 static void
7800 set_variable_part (dataflow_set *set, rtx loc,
7801 decl_or_value dv, HOST_WIDE_INT offset,
7802 enum var_init_status initialized, rtx set_src,
7803 enum insert_option iopt)
7805 variable **slot;
7807 if (iopt == NO_INSERT)
7808 slot = shared_hash_find_slot_noinsert (set->vars, dv);
7809 else
7811 slot = shared_hash_find_slot (set->vars, dv);
7812 if (!slot)
7813 slot = shared_hash_find_slot_unshare (&set->vars, dv, iopt);
7815 set_slot_part (set, loc, slot, dv, offset, initialized, set_src);
7818 /* Remove all recorded register locations for the given variable part
7819 from dataflow set SET, except for those that are identical to loc.
7820 The variable part is specified by variable's declaration or value
7821 DV and offset OFFSET. */
7823 static variable **
7824 clobber_slot_part (dataflow_set *set, rtx loc, variable **slot,
7825 HOST_WIDE_INT offset, rtx set_src)
7827 variable *var = *slot;
7828 int pos = find_variable_location_part (var, offset, NULL);
7830 if (pos >= 0)
7832 location_chain *node, *next;
7834 /* Remove the register locations from the dataflow set. */
7835 next = var->var_part[pos].loc_chain;
7836 for (node = next; node; node = next)
7838 next = node->next;
7839 if (node->loc != loc
7840 && (!flag_var_tracking_uninit
7841 || !set_src
7842 || MEM_P (set_src)
7843 || !rtx_equal_p (set_src, node->set_src)))
7845 if (REG_P (node->loc))
7847 attrs *anode, *anext;
7848 attrs **anextp;
7850 /* Remove the variable part from the register's
7851 list, but preserve any other variable parts
7852 that might be regarded as live in that same
7853 register. */
7854 anextp = &set->regs[REGNO (node->loc)];
7855 for (anode = *anextp; anode; anode = anext)
7857 anext = anode->next;
7858 if (dv_as_opaque (anode->dv) == dv_as_opaque (var->dv)
7859 && anode->offset == offset)
7861 delete anode;
7862 *anextp = anext;
7864 else
7865 anextp = &anode->next;
7869 slot = delete_slot_part (set, node->loc, slot, offset);
7874 return slot;
7877 /* Remove all recorded register locations for the given variable part
7878 from dataflow set SET, except for those that are identical to loc.
7879 The variable part is specified by variable's declaration or value
7880 DV and offset OFFSET. */
7882 static void
7883 clobber_variable_part (dataflow_set *set, rtx loc, decl_or_value dv,
7884 HOST_WIDE_INT offset, rtx set_src)
7886 variable **slot;
7888 if (!dv_as_opaque (dv)
7889 || (!dv_is_value_p (dv) && ! DECL_P (dv_as_decl (dv))))
7890 return;
7892 slot = shared_hash_find_slot_noinsert (set->vars, dv);
7893 if (!slot)
7894 return;
7896 clobber_slot_part (set, loc, slot, offset, set_src);
7899 /* Delete the part of variable's location from dataflow set SET. The
7900 variable part is specified by its SET->vars slot SLOT and offset
7901 OFFSET and the part's location by LOC. */
7903 static variable **
7904 delete_slot_part (dataflow_set *set, rtx loc, variable **slot,
7905 HOST_WIDE_INT offset)
7907 variable *var = *slot;
7908 int pos = find_variable_location_part (var, offset, NULL);
7910 if (pos >= 0)
7912 location_chain *node, *next;
7913 location_chain **nextp;
7914 bool changed;
7915 rtx cur_loc;
7917 if (shared_var_p (var, set->vars))
7919 /* If the variable contains the location part we have to
7920 make a copy of the variable. */
7921 for (node = var->var_part[pos].loc_chain; node;
7922 node = node->next)
7924 if ((REG_P (node->loc) && REG_P (loc)
7925 && REGNO (node->loc) == REGNO (loc))
7926 || rtx_equal_p (node->loc, loc))
7928 slot = unshare_variable (set, slot, var,
7929 VAR_INIT_STATUS_UNKNOWN);
7930 var = *slot;
7931 break;
7936 if (pos == 0 && var->onepart && VAR_LOC_1PAUX (var))
7937 cur_loc = VAR_LOC_FROM (var);
7938 else
7939 cur_loc = var->var_part[pos].cur_loc;
7941 /* Delete the location part. */
7942 changed = false;
7943 nextp = &var->var_part[pos].loc_chain;
7944 for (node = *nextp; node; node = next)
7946 next = node->next;
7947 if ((REG_P (node->loc) && REG_P (loc)
7948 && REGNO (node->loc) == REGNO (loc))
7949 || rtx_equal_p (node->loc, loc))
7951 /* If we have deleted the location which was last emitted
7952 we have to emit new location so add the variable to set
7953 of changed variables. */
7954 if (cur_loc == node->loc)
7956 changed = true;
7957 var->var_part[pos].cur_loc = NULL;
7958 if (pos == 0 && var->onepart && VAR_LOC_1PAUX (var))
7959 VAR_LOC_FROM (var) = NULL;
7961 delete node;
7962 *nextp = next;
7963 break;
7965 else
7966 nextp = &node->next;
7969 if (var->var_part[pos].loc_chain == NULL)
7971 changed = true;
7972 var->n_var_parts--;
7973 while (pos < var->n_var_parts)
7975 var->var_part[pos] = var->var_part[pos + 1];
7976 pos++;
7979 if (changed)
7980 variable_was_changed (var, set);
7983 return slot;
7986 /* Delete the part of variable's location from dataflow set SET. The
7987 variable part is specified by variable's declaration or value DV
7988 and offset OFFSET and the part's location by LOC. */
7990 static void
7991 delete_variable_part (dataflow_set *set, rtx loc, decl_or_value dv,
7992 HOST_WIDE_INT offset)
7994 variable **slot = shared_hash_find_slot_noinsert (set->vars, dv);
7995 if (!slot)
7996 return;
7998 delete_slot_part (set, loc, slot, offset);
8002 /* Structure for passing some other parameters to function
8003 vt_expand_loc_callback. */
8004 struct expand_loc_callback_data
8006 /* The variables and values active at this point. */
8007 variable_table_type *vars;
8009 /* Stack of values and debug_exprs under expansion, and their
8010 children. */
8011 auto_vec<rtx, 4> expanding;
8013 /* Stack of values and debug_exprs whose expansion hit recursion
8014 cycles. They will have VALUE_RECURSED_INTO marked when added to
8015 this list. This flag will be cleared if any of its dependencies
8016 resolves to a valid location. So, if the flag remains set at the
8017 end of the search, we know no valid location for this one can
8018 possibly exist. */
8019 auto_vec<rtx, 4> pending;
8021 /* The maximum depth among the sub-expressions under expansion.
8022 Zero indicates no expansion so far. */
8023 expand_depth depth;
8026 /* Allocate the one-part auxiliary data structure for VAR, with enough
8027 room for COUNT dependencies. */
8029 static void
8030 loc_exp_dep_alloc (variable *var, int count)
8032 size_t allocsize;
8034 gcc_checking_assert (var->onepart);
8036 /* We can be called with COUNT == 0 to allocate the data structure
8037 without any dependencies, e.g. for the backlinks only. However,
8038 if we are specifying a COUNT, then the dependency list must have
8039 been emptied before. It would be possible to adjust pointers or
8040 force it empty here, but this is better done at an earlier point
8041 in the algorithm, so we instead leave an assertion to catch
8042 errors. */
8043 gcc_checking_assert (!count
8044 || VAR_LOC_DEP_VEC (var) == NULL
8045 || VAR_LOC_DEP_VEC (var)->is_empty ());
8047 if (VAR_LOC_1PAUX (var) && VAR_LOC_DEP_VEC (var)->space (count))
8048 return;
8050 allocsize = offsetof (struct onepart_aux, deps)
8051 + vec<loc_exp_dep, va_heap, vl_embed>::embedded_size (count);
8053 if (VAR_LOC_1PAUX (var))
8055 VAR_LOC_1PAUX (var) = XRESIZEVAR (struct onepart_aux,
8056 VAR_LOC_1PAUX (var), allocsize);
8057 /* If the reallocation moves the onepaux structure, the
8058 back-pointer to BACKLINKS in the first list member will still
8059 point to its old location. Adjust it. */
8060 if (VAR_LOC_DEP_LST (var))
8061 VAR_LOC_DEP_LST (var)->pprev = VAR_LOC_DEP_LSTP (var);
8063 else
8065 VAR_LOC_1PAUX (var) = XNEWVAR (struct onepart_aux, allocsize);
8066 *VAR_LOC_DEP_LSTP (var) = NULL;
8067 VAR_LOC_FROM (var) = NULL;
8068 VAR_LOC_DEPTH (var).complexity = 0;
8069 VAR_LOC_DEPTH (var).entryvals = 0;
8071 VAR_LOC_DEP_VEC (var)->embedded_init (count);
8074 /* Remove all entries from the vector of active dependencies of VAR,
8075 removing them from the back-links lists too. */
8077 static void
8078 loc_exp_dep_clear (variable *var)
8080 while (VAR_LOC_DEP_VEC (var) && !VAR_LOC_DEP_VEC (var)->is_empty ())
8082 loc_exp_dep *led = &VAR_LOC_DEP_VEC (var)->last ();
8083 if (led->next)
8084 led->next->pprev = led->pprev;
8085 if (led->pprev)
8086 *led->pprev = led->next;
8087 VAR_LOC_DEP_VEC (var)->pop ();
8091 /* Insert an active dependency from VAR on X to the vector of
8092 dependencies, and add the corresponding back-link to X's list of
8093 back-links in VARS. */
8095 static void
8096 loc_exp_insert_dep (variable *var, rtx x, variable_table_type *vars)
8098 decl_or_value dv;
8099 variable *xvar;
8100 loc_exp_dep *led;
8102 dv = dv_from_rtx (x);
8104 /* ??? Build a vector of variables parallel to EXPANDING, to avoid
8105 an additional look up? */
8106 xvar = vars->find_with_hash (dv, dv_htab_hash (dv));
8108 if (!xvar)
8110 xvar = variable_from_dropped (dv, NO_INSERT);
8111 gcc_checking_assert (xvar);
8114 /* No point in adding the same backlink more than once. This may
8115 arise if say the same value appears in two complex expressions in
8116 the same loc_list, or even more than once in a single
8117 expression. */
8118 if (VAR_LOC_DEP_LST (xvar) && VAR_LOC_DEP_LST (xvar)->dv == var->dv)
8119 return;
8121 if (var->onepart == NOT_ONEPART)
8122 led = new loc_exp_dep;
8123 else
8125 loc_exp_dep empty;
8126 memset (&empty, 0, sizeof (empty));
8127 VAR_LOC_DEP_VEC (var)->quick_push (empty);
8128 led = &VAR_LOC_DEP_VEC (var)->last ();
8130 led->dv = var->dv;
8131 led->value = x;
8133 loc_exp_dep_alloc (xvar, 0);
8134 led->pprev = VAR_LOC_DEP_LSTP (xvar);
8135 led->next = *led->pprev;
8136 if (led->next)
8137 led->next->pprev = &led->next;
8138 *led->pprev = led;
8141 /* Create active dependencies of VAR on COUNT values starting at
8142 VALUE, and corresponding back-links to the entries in VARS. Return
8143 true if we found any pending-recursion results. */
8145 static bool
8146 loc_exp_dep_set (variable *var, rtx result, rtx *value, int count,
8147 variable_table_type *vars)
8149 bool pending_recursion = false;
8151 gcc_checking_assert (VAR_LOC_DEP_VEC (var) == NULL
8152 || VAR_LOC_DEP_VEC (var)->is_empty ());
8154 /* Set up all dependencies from last_child (as set up at the end of
8155 the loop above) to the end. */
8156 loc_exp_dep_alloc (var, count);
8158 while (count--)
8160 rtx x = *value++;
8162 if (!pending_recursion)
8163 pending_recursion = !result && VALUE_RECURSED_INTO (x);
8165 loc_exp_insert_dep (var, x, vars);
8168 return pending_recursion;
8171 /* Notify the back-links of IVAR that are pending recursion that we
8172 have found a non-NIL value for it, so they are cleared for another
8173 attempt to compute a current location. */
8175 static void
8176 notify_dependents_of_resolved_value (variable *ivar, variable_table_type *vars)
8178 loc_exp_dep *led, *next;
8180 for (led = VAR_LOC_DEP_LST (ivar); led; led = next)
8182 decl_or_value dv = led->dv;
8183 variable *var;
8185 next = led->next;
8187 if (dv_is_value_p (dv))
8189 rtx value = dv_as_value (dv);
8191 /* If we have already resolved it, leave it alone. */
8192 if (!VALUE_RECURSED_INTO (value))
8193 continue;
8195 /* Check that VALUE_RECURSED_INTO, true from the test above,
8196 implies NO_LOC_P. */
8197 gcc_checking_assert (NO_LOC_P (value));
8199 /* We won't notify variables that are being expanded,
8200 because their dependency list is cleared before
8201 recursing. */
8202 NO_LOC_P (value) = false;
8203 VALUE_RECURSED_INTO (value) = false;
8205 gcc_checking_assert (dv_changed_p (dv));
8207 else
8209 gcc_checking_assert (dv_onepart_p (dv) != NOT_ONEPART);
8210 if (!dv_changed_p (dv))
8211 continue;
8214 var = vars->find_with_hash (dv, dv_htab_hash (dv));
8216 if (!var)
8217 var = variable_from_dropped (dv, NO_INSERT);
8219 if (var)
8220 notify_dependents_of_resolved_value (var, vars);
8222 if (next)
8223 next->pprev = led->pprev;
8224 if (led->pprev)
8225 *led->pprev = next;
8226 led->next = NULL;
8227 led->pprev = NULL;
8231 static rtx vt_expand_loc_callback (rtx x, bitmap regs,
8232 int max_depth, void *data);
8234 /* Return the combined depth, when one sub-expression evaluated to
8235 BEST_DEPTH and the previous known depth was SAVED_DEPTH. */
8237 static inline expand_depth
8238 update_depth (expand_depth saved_depth, expand_depth best_depth)
8240 /* If we didn't find anything, stick with what we had. */
8241 if (!best_depth.complexity)
8242 return saved_depth;
8244 /* If we found hadn't found anything, use the depth of the current
8245 expression. Do NOT add one extra level, we want to compute the
8246 maximum depth among sub-expressions. We'll increment it later,
8247 if appropriate. */
8248 if (!saved_depth.complexity)
8249 return best_depth;
8251 /* Combine the entryval count so that regardless of which one we
8252 return, the entryval count is accurate. */
8253 best_depth.entryvals = saved_depth.entryvals
8254 = best_depth.entryvals + saved_depth.entryvals;
8256 if (saved_depth.complexity < best_depth.complexity)
8257 return best_depth;
8258 else
8259 return saved_depth;
8262 /* Expand VAR to a location RTX, updating its cur_loc. Use REGS and
8263 DATA for cselib expand callback. If PENDRECP is given, indicate in
8264 it whether any sub-expression couldn't be fully evaluated because
8265 it is pending recursion resolution. */
8267 static inline rtx
8268 vt_expand_var_loc_chain (variable *var, bitmap regs, void *data,
8269 bool *pendrecp)
8271 struct expand_loc_callback_data *elcd
8272 = (struct expand_loc_callback_data *) data;
8273 location_chain *loc, *next;
8274 rtx result = NULL;
8275 int first_child, result_first_child, last_child;
8276 bool pending_recursion;
8277 rtx loc_from = NULL;
8278 struct elt_loc_list *cloc = NULL;
8279 expand_depth depth = { 0, 0 }, saved_depth = elcd->depth;
8280 int wanted_entryvals, found_entryvals = 0;
8282 /* Clear all backlinks pointing at this, so that we're not notified
8283 while we're active. */
8284 loc_exp_dep_clear (var);
8286 retry:
8287 if (var->onepart == ONEPART_VALUE)
8289 cselib_val *val = CSELIB_VAL_PTR (dv_as_value (var->dv));
8291 gcc_checking_assert (cselib_preserved_value_p (val));
8293 cloc = val->locs;
8296 first_child = result_first_child = last_child
8297 = elcd->expanding.length ();
8299 wanted_entryvals = found_entryvals;
8301 /* Attempt to expand each available location in turn. */
8302 for (next = loc = var->n_var_parts ? var->var_part[0].loc_chain : NULL;
8303 loc || cloc; loc = next)
8305 result_first_child = last_child;
8307 if (!loc)
8309 loc_from = cloc->loc;
8310 next = loc;
8311 cloc = cloc->next;
8312 if (unsuitable_loc (loc_from))
8313 continue;
8315 else
8317 loc_from = loc->loc;
8318 next = loc->next;
8321 gcc_checking_assert (!unsuitable_loc (loc_from));
8323 elcd->depth.complexity = elcd->depth.entryvals = 0;
8324 result = cselib_expand_value_rtx_cb (loc_from, regs, EXPR_DEPTH,
8325 vt_expand_loc_callback, data);
8326 last_child = elcd->expanding.length ();
8328 if (result)
8330 depth = elcd->depth;
8332 gcc_checking_assert (depth.complexity
8333 || result_first_child == last_child);
8335 if (last_child - result_first_child != 1)
8337 if (!depth.complexity && GET_CODE (result) == ENTRY_VALUE)
8338 depth.entryvals++;
8339 depth.complexity++;
8342 if (depth.complexity <= EXPR_USE_DEPTH)
8344 if (depth.entryvals <= wanted_entryvals)
8345 break;
8346 else if (!found_entryvals || depth.entryvals < found_entryvals)
8347 found_entryvals = depth.entryvals;
8350 result = NULL;
8353 /* Set it up in case we leave the loop. */
8354 depth.complexity = depth.entryvals = 0;
8355 loc_from = NULL;
8356 result_first_child = first_child;
8359 if (!loc_from && wanted_entryvals < found_entryvals)
8361 /* We found entries with ENTRY_VALUEs and skipped them. Since
8362 we could not find any expansions without ENTRY_VALUEs, but we
8363 found at least one with them, go back and get an entry with
8364 the minimum number ENTRY_VALUE count that we found. We could
8365 avoid looping, but since each sub-loc is already resolved,
8366 the re-expansion should be trivial. ??? Should we record all
8367 attempted locs as dependencies, so that we retry the
8368 expansion should any of them change, in the hope it can give
8369 us a new entry without an ENTRY_VALUE? */
8370 elcd->expanding.truncate (first_child);
8371 goto retry;
8374 /* Register all encountered dependencies as active. */
8375 pending_recursion = loc_exp_dep_set
8376 (var, result, elcd->expanding.address () + result_first_child,
8377 last_child - result_first_child, elcd->vars);
8379 elcd->expanding.truncate (first_child);
8381 /* Record where the expansion came from. */
8382 gcc_checking_assert (!result || !pending_recursion);
8383 VAR_LOC_FROM (var) = loc_from;
8384 VAR_LOC_DEPTH (var) = depth;
8386 gcc_checking_assert (!depth.complexity == !result);
8388 elcd->depth = update_depth (saved_depth, depth);
8390 /* Indicate whether any of the dependencies are pending recursion
8391 resolution. */
8392 if (pendrecp)
8393 *pendrecp = pending_recursion;
8395 if (!pendrecp || !pending_recursion)
8396 var->var_part[0].cur_loc = result;
8398 return result;
8401 /* Callback for cselib_expand_value, that looks for expressions
8402 holding the value in the var-tracking hash tables. Return X for
8403 standard processing, anything else is to be used as-is. */
8405 static rtx
8406 vt_expand_loc_callback (rtx x, bitmap regs,
8407 int max_depth ATTRIBUTE_UNUSED,
8408 void *data)
8410 struct expand_loc_callback_data *elcd
8411 = (struct expand_loc_callback_data *) data;
8412 decl_or_value dv;
8413 variable *var;
8414 rtx result, subreg;
8415 bool pending_recursion = false;
8416 bool from_empty = false;
8418 switch (GET_CODE (x))
8420 case SUBREG:
8421 subreg = cselib_expand_value_rtx_cb (SUBREG_REG (x), regs,
8422 EXPR_DEPTH,
8423 vt_expand_loc_callback, data);
8425 if (!subreg)
8426 return NULL;
8428 result = simplify_gen_subreg (GET_MODE (x), subreg,
8429 GET_MODE (SUBREG_REG (x)),
8430 SUBREG_BYTE (x));
8432 /* Invalid SUBREGs are ok in debug info. ??? We could try
8433 alternate expansions for the VALUE as well. */
8434 if (!result)
8435 result = gen_rtx_raw_SUBREG (GET_MODE (x), subreg, SUBREG_BYTE (x));
8437 return result;
8439 case DEBUG_EXPR:
8440 case VALUE:
8441 dv = dv_from_rtx (x);
8442 break;
8444 default:
8445 return x;
8448 elcd->expanding.safe_push (x);
8450 /* Check that VALUE_RECURSED_INTO implies NO_LOC_P. */
8451 gcc_checking_assert (!VALUE_RECURSED_INTO (x) || NO_LOC_P (x));
8453 if (NO_LOC_P (x))
8455 gcc_checking_assert (VALUE_RECURSED_INTO (x) || !dv_changed_p (dv));
8456 return NULL;
8459 var = elcd->vars->find_with_hash (dv, dv_htab_hash (dv));
8461 if (!var)
8463 from_empty = true;
8464 var = variable_from_dropped (dv, INSERT);
8467 gcc_checking_assert (var);
8469 if (!dv_changed_p (dv))
8471 gcc_checking_assert (!NO_LOC_P (x));
8472 gcc_checking_assert (var->var_part[0].cur_loc);
8473 gcc_checking_assert (VAR_LOC_1PAUX (var));
8474 gcc_checking_assert (VAR_LOC_1PAUX (var)->depth.complexity);
8476 elcd->depth = update_depth (elcd->depth, VAR_LOC_1PAUX (var)->depth);
8478 return var->var_part[0].cur_loc;
8481 VALUE_RECURSED_INTO (x) = true;
8482 /* This is tentative, but it makes some tests simpler. */
8483 NO_LOC_P (x) = true;
8485 gcc_checking_assert (var->n_var_parts == 1 || from_empty);
8487 result = vt_expand_var_loc_chain (var, regs, data, &pending_recursion);
8489 if (pending_recursion)
8491 gcc_checking_assert (!result);
8492 elcd->pending.safe_push (x);
8494 else
8496 NO_LOC_P (x) = !result;
8497 VALUE_RECURSED_INTO (x) = false;
8498 set_dv_changed (dv, false);
8500 if (result)
8501 notify_dependents_of_resolved_value (var, elcd->vars);
8504 return result;
8507 /* While expanding variables, we may encounter recursion cycles
8508 because of mutual (possibly indirect) dependencies between two
8509 particular variables (or values), say A and B. If we're trying to
8510 expand A when we get to B, which in turn attempts to expand A, if
8511 we can't find any other expansion for B, we'll add B to this
8512 pending-recursion stack, and tentatively return NULL for its
8513 location. This tentative value will be used for any other
8514 occurrences of B, unless A gets some other location, in which case
8515 it will notify B that it is worth another try at computing a
8516 location for it, and it will use the location computed for A then.
8517 At the end of the expansion, the tentative NULL locations become
8518 final for all members of PENDING that didn't get a notification.
8519 This function performs this finalization of NULL locations. */
8521 static void
8522 resolve_expansions_pending_recursion (vec<rtx, va_heap> *pending)
8524 while (!pending->is_empty ())
8526 rtx x = pending->pop ();
8527 decl_or_value dv;
8529 if (!VALUE_RECURSED_INTO (x))
8530 continue;
8532 gcc_checking_assert (NO_LOC_P (x));
8533 VALUE_RECURSED_INTO (x) = false;
8534 dv = dv_from_rtx (x);
8535 gcc_checking_assert (dv_changed_p (dv));
8536 set_dv_changed (dv, false);
8540 /* Initialize expand_loc_callback_data D with variable hash table V.
8541 It must be a macro because of alloca (vec stack). */
8542 #define INIT_ELCD(d, v) \
8543 do \
8545 (d).vars = (v); \
8546 (d).depth.complexity = (d).depth.entryvals = 0; \
8548 while (0)
8549 /* Finalize expand_loc_callback_data D, resolved to location L. */
8550 #define FINI_ELCD(d, l) \
8551 do \
8553 resolve_expansions_pending_recursion (&(d).pending); \
8554 (d).pending.release (); \
8555 (d).expanding.release (); \
8557 if ((l) && MEM_P (l)) \
8558 (l) = targetm.delegitimize_address (l); \
8560 while (0)
8562 /* Expand VALUEs and DEBUG_EXPRs in LOC to a location, using the
8563 equivalences in VARS, updating their CUR_LOCs in the process. */
8565 static rtx
8566 vt_expand_loc (rtx loc, variable_table_type *vars)
8568 struct expand_loc_callback_data data;
8569 rtx result;
8571 if (!MAY_HAVE_DEBUG_INSNS)
8572 return loc;
8574 INIT_ELCD (data, vars);
8576 result = cselib_expand_value_rtx_cb (loc, scratch_regs, EXPR_DEPTH,
8577 vt_expand_loc_callback, &data);
8579 FINI_ELCD (data, result);
8581 return result;
8584 /* Expand the one-part VARiable to a location, using the equivalences
8585 in VARS, updating their CUR_LOCs in the process. */
8587 static rtx
8588 vt_expand_1pvar (variable *var, variable_table_type *vars)
8590 struct expand_loc_callback_data data;
8591 rtx loc;
8593 gcc_checking_assert (var->onepart && var->n_var_parts == 1);
8595 if (!dv_changed_p (var->dv))
8596 return var->var_part[0].cur_loc;
8598 INIT_ELCD (data, vars);
8600 loc = vt_expand_var_loc_chain (var, scratch_regs, &data, NULL);
8602 gcc_checking_assert (data.expanding.is_empty ());
8604 FINI_ELCD (data, loc);
8606 return loc;
8609 /* Emit the NOTE_INSN_VAR_LOCATION for variable *VARP. DATA contains
8610 additional parameters: WHERE specifies whether the note shall be emitted
8611 before or after instruction INSN. */
8614 emit_note_insn_var_location (variable **varp, emit_note_data *data)
8616 variable *var = *varp;
8617 rtx_insn *insn = data->insn;
8618 enum emit_note_where where = data->where;
8619 variable_table_type *vars = data->vars;
8620 rtx_note *note;
8621 rtx note_vl;
8622 int i, j, n_var_parts;
8623 bool complete;
8624 enum var_init_status initialized = VAR_INIT_STATUS_UNINITIALIZED;
8625 HOST_WIDE_INT last_limit;
8626 tree type_size_unit;
8627 HOST_WIDE_INT offsets[MAX_VAR_PARTS];
8628 rtx loc[MAX_VAR_PARTS];
8629 tree decl;
8630 location_chain *lc;
8632 gcc_checking_assert (var->onepart == NOT_ONEPART
8633 || var->onepart == ONEPART_VDECL);
8635 decl = dv_as_decl (var->dv);
8637 complete = true;
8638 last_limit = 0;
8639 n_var_parts = 0;
8640 if (!var->onepart)
8641 for (i = 0; i < var->n_var_parts; i++)
8642 if (var->var_part[i].cur_loc == NULL && var->var_part[i].loc_chain)
8643 var->var_part[i].cur_loc = var->var_part[i].loc_chain->loc;
8644 for (i = 0; i < var->n_var_parts; i++)
8646 machine_mode mode, wider_mode;
8647 rtx loc2;
8648 HOST_WIDE_INT offset;
8650 if (i == 0 && var->onepart)
8652 gcc_checking_assert (var->n_var_parts == 1);
8653 offset = 0;
8654 initialized = VAR_INIT_STATUS_INITIALIZED;
8655 loc2 = vt_expand_1pvar (var, vars);
8657 else
8659 if (last_limit < VAR_PART_OFFSET (var, i))
8661 complete = false;
8662 break;
8664 else if (last_limit > VAR_PART_OFFSET (var, i))
8665 continue;
8666 offset = VAR_PART_OFFSET (var, i);
8667 loc2 = var->var_part[i].cur_loc;
8668 if (loc2 && GET_CODE (loc2) == MEM
8669 && GET_CODE (XEXP (loc2, 0)) == VALUE)
8671 rtx depval = XEXP (loc2, 0);
8673 loc2 = vt_expand_loc (loc2, vars);
8675 if (loc2)
8676 loc_exp_insert_dep (var, depval, vars);
8678 if (!loc2)
8680 complete = false;
8681 continue;
8683 gcc_checking_assert (GET_CODE (loc2) != VALUE);
8684 for (lc = var->var_part[i].loc_chain; lc; lc = lc->next)
8685 if (var->var_part[i].cur_loc == lc->loc)
8687 initialized = lc->init;
8688 break;
8690 gcc_assert (lc);
8693 offsets[n_var_parts] = offset;
8694 if (!loc2)
8696 complete = false;
8697 continue;
8699 loc[n_var_parts] = loc2;
8700 mode = GET_MODE (var->var_part[i].cur_loc);
8701 if (mode == VOIDmode && var->onepart)
8702 mode = DECL_MODE (decl);
8703 last_limit = offsets[n_var_parts] + GET_MODE_SIZE (mode);
8705 /* Attempt to merge adjacent registers or memory. */
8706 wider_mode = GET_MODE_WIDER_MODE (mode);
8707 for (j = i + 1; j < var->n_var_parts; j++)
8708 if (last_limit <= VAR_PART_OFFSET (var, j))
8709 break;
8710 if (j < var->n_var_parts
8711 && wider_mode != VOIDmode
8712 && var->var_part[j].cur_loc
8713 && mode == GET_MODE (var->var_part[j].cur_loc)
8714 && (REG_P (loc[n_var_parts]) || MEM_P (loc[n_var_parts]))
8715 && last_limit == (var->onepart ? 0 : VAR_PART_OFFSET (var, j))
8716 && (loc2 = vt_expand_loc (var->var_part[j].cur_loc, vars))
8717 && GET_CODE (loc[n_var_parts]) == GET_CODE (loc2))
8719 rtx new_loc = NULL;
8721 if (REG_P (loc[n_var_parts])
8722 && hard_regno_nregs[REGNO (loc[n_var_parts])][mode] * 2
8723 == hard_regno_nregs[REGNO (loc[n_var_parts])][wider_mode]
8724 && end_hard_regno (mode, REGNO (loc[n_var_parts]))
8725 == REGNO (loc2))
8727 if (! WORDS_BIG_ENDIAN && ! BYTES_BIG_ENDIAN)
8728 new_loc = simplify_subreg (wider_mode, loc[n_var_parts],
8729 mode, 0);
8730 else if (WORDS_BIG_ENDIAN && BYTES_BIG_ENDIAN)
8731 new_loc = simplify_subreg (wider_mode, loc2, mode, 0);
8732 if (new_loc)
8734 if (!REG_P (new_loc)
8735 || REGNO (new_loc) != REGNO (loc[n_var_parts]))
8736 new_loc = NULL;
8737 else
8738 REG_ATTRS (new_loc) = REG_ATTRS (loc[n_var_parts]);
8741 else if (MEM_P (loc[n_var_parts])
8742 && GET_CODE (XEXP (loc2, 0)) == PLUS
8743 && REG_P (XEXP (XEXP (loc2, 0), 0))
8744 && CONST_INT_P (XEXP (XEXP (loc2, 0), 1)))
8746 if ((REG_P (XEXP (loc[n_var_parts], 0))
8747 && rtx_equal_p (XEXP (loc[n_var_parts], 0),
8748 XEXP (XEXP (loc2, 0), 0))
8749 && INTVAL (XEXP (XEXP (loc2, 0), 1))
8750 == GET_MODE_SIZE (mode))
8751 || (GET_CODE (XEXP (loc[n_var_parts], 0)) == PLUS
8752 && CONST_INT_P (XEXP (XEXP (loc[n_var_parts], 0), 1))
8753 && rtx_equal_p (XEXP (XEXP (loc[n_var_parts], 0), 0),
8754 XEXP (XEXP (loc2, 0), 0))
8755 && INTVAL (XEXP (XEXP (loc[n_var_parts], 0), 1))
8756 + GET_MODE_SIZE (mode)
8757 == INTVAL (XEXP (XEXP (loc2, 0), 1))))
8758 new_loc = adjust_address_nv (loc[n_var_parts],
8759 wider_mode, 0);
8762 if (new_loc)
8764 loc[n_var_parts] = new_loc;
8765 mode = wider_mode;
8766 last_limit = offsets[n_var_parts] + GET_MODE_SIZE (mode);
8767 i = j;
8770 ++n_var_parts;
8772 type_size_unit = TYPE_SIZE_UNIT (TREE_TYPE (decl));
8773 if ((unsigned HOST_WIDE_INT) last_limit < TREE_INT_CST_LOW (type_size_unit))
8774 complete = false;
8776 if (! flag_var_tracking_uninit)
8777 initialized = VAR_INIT_STATUS_INITIALIZED;
8779 note_vl = NULL_RTX;
8780 if (!complete)
8781 note_vl = gen_rtx_VAR_LOCATION (VOIDmode, decl, NULL_RTX, initialized);
8782 else if (n_var_parts == 1)
8784 rtx expr_list;
8786 if (offsets[0] || GET_CODE (loc[0]) == PARALLEL)
8787 expr_list = gen_rtx_EXPR_LIST (VOIDmode, loc[0], GEN_INT (offsets[0]));
8788 else
8789 expr_list = loc[0];
8791 note_vl = gen_rtx_VAR_LOCATION (VOIDmode, decl, expr_list, initialized);
8793 else if (n_var_parts)
8795 rtx parallel;
8797 for (i = 0; i < n_var_parts; i++)
8798 loc[i]
8799 = gen_rtx_EXPR_LIST (VOIDmode, loc[i], GEN_INT (offsets[i]));
8801 parallel = gen_rtx_PARALLEL (VOIDmode,
8802 gen_rtvec_v (n_var_parts, loc));
8803 note_vl = gen_rtx_VAR_LOCATION (VOIDmode, decl,
8804 parallel, initialized);
8807 if (where != EMIT_NOTE_BEFORE_INSN)
8809 note = emit_note_after (NOTE_INSN_VAR_LOCATION, insn);
8810 if (where == EMIT_NOTE_AFTER_CALL_INSN)
8811 NOTE_DURING_CALL_P (note) = true;
8813 else
8815 /* Make sure that the call related notes come first. */
8816 while (NEXT_INSN (insn)
8817 && NOTE_P (insn)
8818 && ((NOTE_KIND (insn) == NOTE_INSN_VAR_LOCATION
8819 && NOTE_DURING_CALL_P (insn))
8820 || NOTE_KIND (insn) == NOTE_INSN_CALL_ARG_LOCATION))
8821 insn = NEXT_INSN (insn);
8822 if (NOTE_P (insn)
8823 && ((NOTE_KIND (insn) == NOTE_INSN_VAR_LOCATION
8824 && NOTE_DURING_CALL_P (insn))
8825 || NOTE_KIND (insn) == NOTE_INSN_CALL_ARG_LOCATION))
8826 note = emit_note_after (NOTE_INSN_VAR_LOCATION, insn);
8827 else
8828 note = emit_note_before (NOTE_INSN_VAR_LOCATION, insn);
8830 NOTE_VAR_LOCATION (note) = note_vl;
8832 set_dv_changed (var->dv, false);
8833 gcc_assert (var->in_changed_variables);
8834 var->in_changed_variables = false;
8835 changed_variables->clear_slot (varp);
8837 /* Continue traversing the hash table. */
8838 return 1;
8841 /* While traversing changed_variables, push onto DATA (a stack of RTX
8842 values) entries that aren't user variables. */
8845 var_track_values_to_stack (variable **slot,
8846 vec<rtx, va_heap> *changed_values_stack)
8848 variable *var = *slot;
8850 if (var->onepart == ONEPART_VALUE)
8851 changed_values_stack->safe_push (dv_as_value (var->dv));
8852 else if (var->onepart == ONEPART_DEXPR)
8853 changed_values_stack->safe_push (DECL_RTL_KNOWN_SET (dv_as_decl (var->dv)));
8855 return 1;
8858 /* Remove from changed_variables the entry whose DV corresponds to
8859 value or debug_expr VAL. */
8860 static void
8861 remove_value_from_changed_variables (rtx val)
8863 decl_or_value dv = dv_from_rtx (val);
8864 variable **slot;
8865 variable *var;
8867 slot = changed_variables->find_slot_with_hash (dv, dv_htab_hash (dv),
8868 NO_INSERT);
8869 var = *slot;
8870 var->in_changed_variables = false;
8871 changed_variables->clear_slot (slot);
8874 /* If VAL (a value or debug_expr) has backlinks to variables actively
8875 dependent on it in HTAB or in CHANGED_VARIABLES, mark them as
8876 changed, adding to CHANGED_VALUES_STACK any dependencies that may
8877 have dependencies of their own to notify. */
8879 static void
8880 notify_dependents_of_changed_value (rtx val, variable_table_type *htab,
8881 vec<rtx, va_heap> *changed_values_stack)
8883 variable **slot;
8884 variable *var;
8885 loc_exp_dep *led;
8886 decl_or_value dv = dv_from_rtx (val);
8888 slot = changed_variables->find_slot_with_hash (dv, dv_htab_hash (dv),
8889 NO_INSERT);
8890 if (!slot)
8891 slot = htab->find_slot_with_hash (dv, dv_htab_hash (dv), NO_INSERT);
8892 if (!slot)
8893 slot = dropped_values->find_slot_with_hash (dv, dv_htab_hash (dv),
8894 NO_INSERT);
8895 var = *slot;
8897 while ((led = VAR_LOC_DEP_LST (var)))
8899 decl_or_value ldv = led->dv;
8900 variable *ivar;
8902 /* Deactivate and remove the backlink, as it was “used up”. It
8903 makes no sense to attempt to notify the same entity again:
8904 either it will be recomputed and re-register an active
8905 dependency, or it will still have the changed mark. */
8906 if (led->next)
8907 led->next->pprev = led->pprev;
8908 if (led->pprev)
8909 *led->pprev = led->next;
8910 led->next = NULL;
8911 led->pprev = NULL;
8913 if (dv_changed_p (ldv))
8914 continue;
8916 switch (dv_onepart_p (ldv))
8918 case ONEPART_VALUE:
8919 case ONEPART_DEXPR:
8920 set_dv_changed (ldv, true);
8921 changed_values_stack->safe_push (dv_as_rtx (ldv));
8922 break;
8924 case ONEPART_VDECL:
8925 ivar = htab->find_with_hash (ldv, dv_htab_hash (ldv));
8926 gcc_checking_assert (!VAR_LOC_DEP_LST (ivar));
8927 variable_was_changed (ivar, NULL);
8928 break;
8930 case NOT_ONEPART:
8931 delete led;
8932 ivar = htab->find_with_hash (ldv, dv_htab_hash (ldv));
8933 if (ivar)
8935 int i = ivar->n_var_parts;
8936 while (i--)
8938 rtx loc = ivar->var_part[i].cur_loc;
8940 if (loc && GET_CODE (loc) == MEM
8941 && XEXP (loc, 0) == val)
8943 variable_was_changed (ivar, NULL);
8944 break;
8948 break;
8950 default:
8951 gcc_unreachable ();
8956 /* Take out of changed_variables any entries that don't refer to use
8957 variables. Back-propagate change notifications from values and
8958 debug_exprs to their active dependencies in HTAB or in
8959 CHANGED_VARIABLES. */
8961 static void
8962 process_changed_values (variable_table_type *htab)
8964 int i, n;
8965 rtx val;
8966 auto_vec<rtx, 20> changed_values_stack;
8968 /* Move values from changed_variables to changed_values_stack. */
8969 changed_variables
8970 ->traverse <vec<rtx, va_heap>*, var_track_values_to_stack>
8971 (&changed_values_stack);
8973 /* Back-propagate change notifications in values while popping
8974 them from the stack. */
8975 for (n = i = changed_values_stack.length ();
8976 i > 0; i = changed_values_stack.length ())
8978 val = changed_values_stack.pop ();
8979 notify_dependents_of_changed_value (val, htab, &changed_values_stack);
8981 /* This condition will hold when visiting each of the entries
8982 originally in changed_variables. We can't remove them
8983 earlier because this could drop the backlinks before we got a
8984 chance to use them. */
8985 if (i == n)
8987 remove_value_from_changed_variables (val);
8988 n--;
8993 /* Emit NOTE_INSN_VAR_LOCATION note for each variable from a chain
8994 CHANGED_VARIABLES and delete this chain. WHERE specifies whether
8995 the notes shall be emitted before of after instruction INSN. */
8997 static void
8998 emit_notes_for_changes (rtx_insn *insn, enum emit_note_where where,
8999 shared_hash *vars)
9001 emit_note_data data;
9002 variable_table_type *htab = shared_hash_htab (vars);
9004 if (!changed_variables->elements ())
9005 return;
9007 if (MAY_HAVE_DEBUG_INSNS)
9008 process_changed_values (htab);
9010 data.insn = insn;
9011 data.where = where;
9012 data.vars = htab;
9014 changed_variables
9015 ->traverse <emit_note_data*, emit_note_insn_var_location> (&data);
9018 /* Add variable *SLOT to the chain CHANGED_VARIABLES if it differs from the
9019 same variable in hash table DATA or is not there at all. */
9022 emit_notes_for_differences_1 (variable **slot, variable_table_type *new_vars)
9024 variable *old_var, *new_var;
9026 old_var = *slot;
9027 new_var = new_vars->find_with_hash (old_var->dv, dv_htab_hash (old_var->dv));
9029 if (!new_var)
9031 /* Variable has disappeared. */
9032 variable *empty_var = NULL;
9034 if (old_var->onepart == ONEPART_VALUE
9035 || old_var->onepart == ONEPART_DEXPR)
9037 empty_var = variable_from_dropped (old_var->dv, NO_INSERT);
9038 if (empty_var)
9040 gcc_checking_assert (!empty_var->in_changed_variables);
9041 if (!VAR_LOC_1PAUX (old_var))
9043 VAR_LOC_1PAUX (old_var) = VAR_LOC_1PAUX (empty_var);
9044 VAR_LOC_1PAUX (empty_var) = NULL;
9046 else
9047 gcc_checking_assert (!VAR_LOC_1PAUX (empty_var));
9051 if (!empty_var)
9053 empty_var = onepart_pool_allocate (old_var->onepart);
9054 empty_var->dv = old_var->dv;
9055 empty_var->refcount = 0;
9056 empty_var->n_var_parts = 0;
9057 empty_var->onepart = old_var->onepart;
9058 empty_var->in_changed_variables = false;
9061 if (empty_var->onepart)
9063 /* Propagate the auxiliary data to (ultimately)
9064 changed_variables. */
9065 empty_var->var_part[0].loc_chain = NULL;
9066 empty_var->var_part[0].cur_loc = NULL;
9067 VAR_LOC_1PAUX (empty_var) = VAR_LOC_1PAUX (old_var);
9068 VAR_LOC_1PAUX (old_var) = NULL;
9070 variable_was_changed (empty_var, NULL);
9071 /* Continue traversing the hash table. */
9072 return 1;
9074 /* Update cur_loc and one-part auxiliary data, before new_var goes
9075 through variable_was_changed. */
9076 if (old_var != new_var && new_var->onepart)
9078 gcc_checking_assert (VAR_LOC_1PAUX (new_var) == NULL);
9079 VAR_LOC_1PAUX (new_var) = VAR_LOC_1PAUX (old_var);
9080 VAR_LOC_1PAUX (old_var) = NULL;
9081 new_var->var_part[0].cur_loc = old_var->var_part[0].cur_loc;
9083 if (variable_different_p (old_var, new_var))
9084 variable_was_changed (new_var, NULL);
9086 /* Continue traversing the hash table. */
9087 return 1;
9090 /* Add variable *SLOT to the chain CHANGED_VARIABLES if it is not in hash
9091 table DATA. */
9094 emit_notes_for_differences_2 (variable **slot, variable_table_type *old_vars)
9096 variable *old_var, *new_var;
9098 new_var = *slot;
9099 old_var = old_vars->find_with_hash (new_var->dv, dv_htab_hash (new_var->dv));
9100 if (!old_var)
9102 int i;
9103 for (i = 0; i < new_var->n_var_parts; i++)
9104 new_var->var_part[i].cur_loc = NULL;
9105 variable_was_changed (new_var, NULL);
9108 /* Continue traversing the hash table. */
9109 return 1;
9112 /* Emit notes before INSN for differences between dataflow sets OLD_SET and
9113 NEW_SET. */
9115 static void
9116 emit_notes_for_differences (rtx_insn *insn, dataflow_set *old_set,
9117 dataflow_set *new_set)
9119 shared_hash_htab (old_set->vars)
9120 ->traverse <variable_table_type *, emit_notes_for_differences_1>
9121 (shared_hash_htab (new_set->vars));
9122 shared_hash_htab (new_set->vars)
9123 ->traverse <variable_table_type *, emit_notes_for_differences_2>
9124 (shared_hash_htab (old_set->vars));
9125 emit_notes_for_changes (insn, EMIT_NOTE_BEFORE_INSN, new_set->vars);
9128 /* Return the next insn after INSN that is not a NOTE_INSN_VAR_LOCATION. */
9130 static rtx_insn *
9131 next_non_note_insn_var_location (rtx_insn *insn)
9133 while (insn)
9135 insn = NEXT_INSN (insn);
9136 if (insn == 0
9137 || !NOTE_P (insn)
9138 || NOTE_KIND (insn) != NOTE_INSN_VAR_LOCATION)
9139 break;
9142 return insn;
9145 /* Emit the notes for changes of location parts in the basic block BB. */
9147 static void
9148 emit_notes_in_bb (basic_block bb, dataflow_set *set)
9150 unsigned int i;
9151 micro_operation *mo;
9153 dataflow_set_clear (set);
9154 dataflow_set_copy (set, &VTI (bb)->in);
9156 FOR_EACH_VEC_ELT (VTI (bb)->mos, i, mo)
9158 rtx_insn *insn = mo->insn;
9159 rtx_insn *next_insn = next_non_note_insn_var_location (insn);
9161 switch (mo->type)
9163 case MO_CALL:
9164 dataflow_set_clear_at_call (set, insn);
9165 emit_notes_for_changes (insn, EMIT_NOTE_AFTER_CALL_INSN, set->vars);
9167 rtx arguments = mo->u.loc, *p = &arguments;
9168 rtx_note *note;
9169 while (*p)
9171 XEXP (XEXP (*p, 0), 1)
9172 = vt_expand_loc (XEXP (XEXP (*p, 0), 1),
9173 shared_hash_htab (set->vars));
9174 /* If expansion is successful, keep it in the list. */
9175 if (XEXP (XEXP (*p, 0), 1))
9176 p = &XEXP (*p, 1);
9177 /* Otherwise, if the following item is data_value for it,
9178 drop it too too. */
9179 else if (XEXP (*p, 1)
9180 && REG_P (XEXP (XEXP (*p, 0), 0))
9181 && MEM_P (XEXP (XEXP (XEXP (*p, 1), 0), 0))
9182 && REG_P (XEXP (XEXP (XEXP (XEXP (*p, 1), 0), 0),
9184 && REGNO (XEXP (XEXP (*p, 0), 0))
9185 == REGNO (XEXP (XEXP (XEXP (XEXP (*p, 1), 0),
9186 0), 0)))
9187 *p = XEXP (XEXP (*p, 1), 1);
9188 /* Just drop this item. */
9189 else
9190 *p = XEXP (*p, 1);
9192 note = emit_note_after (NOTE_INSN_CALL_ARG_LOCATION, insn);
9193 NOTE_VAR_LOCATION (note) = arguments;
9195 break;
9197 case MO_USE:
9199 rtx loc = mo->u.loc;
9201 if (REG_P (loc))
9202 var_reg_set (set, loc, VAR_INIT_STATUS_UNINITIALIZED, NULL);
9203 else
9204 var_mem_set (set, loc, VAR_INIT_STATUS_UNINITIALIZED, NULL);
9206 emit_notes_for_changes (insn, EMIT_NOTE_BEFORE_INSN, set->vars);
9208 break;
9210 case MO_VAL_LOC:
9212 rtx loc = mo->u.loc;
9213 rtx val, vloc;
9214 tree var;
9216 if (GET_CODE (loc) == CONCAT)
9218 val = XEXP (loc, 0);
9219 vloc = XEXP (loc, 1);
9221 else
9223 val = NULL_RTX;
9224 vloc = loc;
9227 var = PAT_VAR_LOCATION_DECL (vloc);
9229 clobber_variable_part (set, NULL_RTX,
9230 dv_from_decl (var), 0, NULL_RTX);
9231 if (val)
9233 if (VAL_NEEDS_RESOLUTION (loc))
9234 val_resolve (set, val, PAT_VAR_LOCATION_LOC (vloc), insn);
9235 set_variable_part (set, val, dv_from_decl (var), 0,
9236 VAR_INIT_STATUS_INITIALIZED, NULL_RTX,
9237 INSERT);
9239 else if (!VAR_LOC_UNKNOWN_P (PAT_VAR_LOCATION_LOC (vloc)))
9240 set_variable_part (set, PAT_VAR_LOCATION_LOC (vloc),
9241 dv_from_decl (var), 0,
9242 VAR_INIT_STATUS_INITIALIZED, NULL_RTX,
9243 INSERT);
9245 emit_notes_for_changes (insn, EMIT_NOTE_AFTER_INSN, set->vars);
9247 break;
9249 case MO_VAL_USE:
9251 rtx loc = mo->u.loc;
9252 rtx val, vloc, uloc;
9254 vloc = uloc = XEXP (loc, 1);
9255 val = XEXP (loc, 0);
9257 if (GET_CODE (val) == CONCAT)
9259 uloc = XEXP (val, 1);
9260 val = XEXP (val, 0);
9263 if (VAL_NEEDS_RESOLUTION (loc))
9264 val_resolve (set, val, vloc, insn);
9265 else
9266 val_store (set, val, uloc, insn, false);
9268 if (VAL_HOLDS_TRACK_EXPR (loc))
9270 if (GET_CODE (uloc) == REG)
9271 var_reg_set (set, uloc, VAR_INIT_STATUS_UNINITIALIZED,
9272 NULL);
9273 else if (GET_CODE (uloc) == MEM)
9274 var_mem_set (set, uloc, VAR_INIT_STATUS_UNINITIALIZED,
9275 NULL);
9278 emit_notes_for_changes (insn, EMIT_NOTE_BEFORE_INSN, set->vars);
9280 break;
9282 case MO_VAL_SET:
9284 rtx loc = mo->u.loc;
9285 rtx val, vloc, uloc;
9286 rtx dstv, srcv;
9288 vloc = loc;
9289 uloc = XEXP (vloc, 1);
9290 val = XEXP (vloc, 0);
9291 vloc = uloc;
9293 if (GET_CODE (uloc) == SET)
9295 dstv = SET_DEST (uloc);
9296 srcv = SET_SRC (uloc);
9298 else
9300 dstv = uloc;
9301 srcv = NULL;
9304 if (GET_CODE (val) == CONCAT)
9306 dstv = vloc = XEXP (val, 1);
9307 val = XEXP (val, 0);
9310 if (GET_CODE (vloc) == SET)
9312 srcv = SET_SRC (vloc);
9314 gcc_assert (val != srcv);
9315 gcc_assert (vloc == uloc || VAL_NEEDS_RESOLUTION (loc));
9317 dstv = vloc = SET_DEST (vloc);
9319 if (VAL_NEEDS_RESOLUTION (loc))
9320 val_resolve (set, val, srcv, insn);
9322 else if (VAL_NEEDS_RESOLUTION (loc))
9324 gcc_assert (GET_CODE (uloc) == SET
9325 && GET_CODE (SET_SRC (uloc)) == REG);
9326 val_resolve (set, val, SET_SRC (uloc), insn);
9329 if (VAL_HOLDS_TRACK_EXPR (loc))
9331 if (VAL_EXPR_IS_CLOBBERED (loc))
9333 if (REG_P (uloc))
9334 var_reg_delete (set, uloc, true);
9335 else if (MEM_P (uloc))
9337 gcc_assert (MEM_P (dstv));
9338 gcc_assert (MEM_ATTRS (dstv) == MEM_ATTRS (uloc));
9339 var_mem_delete (set, dstv, true);
9342 else
9344 bool copied_p = VAL_EXPR_IS_COPIED (loc);
9345 rtx src = NULL, dst = uloc;
9346 enum var_init_status status = VAR_INIT_STATUS_INITIALIZED;
9348 if (GET_CODE (uloc) == SET)
9350 src = SET_SRC (uloc);
9351 dst = SET_DEST (uloc);
9354 if (copied_p)
9356 status = find_src_status (set, src);
9358 src = find_src_set_src (set, src);
9361 if (REG_P (dst))
9362 var_reg_delete_and_set (set, dst, !copied_p,
9363 status, srcv);
9364 else if (MEM_P (dst))
9366 gcc_assert (MEM_P (dstv));
9367 gcc_assert (MEM_ATTRS (dstv) == MEM_ATTRS (dst));
9368 var_mem_delete_and_set (set, dstv, !copied_p,
9369 status, srcv);
9373 else if (REG_P (uloc))
9374 var_regno_delete (set, REGNO (uloc));
9375 else if (MEM_P (uloc))
9377 gcc_checking_assert (GET_CODE (vloc) == MEM);
9378 gcc_checking_assert (vloc == dstv);
9379 if (vloc != dstv)
9380 clobber_overlapping_mems (set, vloc);
9383 val_store (set, val, dstv, insn, true);
9385 emit_notes_for_changes (next_insn, EMIT_NOTE_BEFORE_INSN,
9386 set->vars);
9388 break;
9390 case MO_SET:
9392 rtx loc = mo->u.loc;
9393 rtx set_src = NULL;
9395 if (GET_CODE (loc) == SET)
9397 set_src = SET_SRC (loc);
9398 loc = SET_DEST (loc);
9401 if (REG_P (loc))
9402 var_reg_delete_and_set (set, loc, true, VAR_INIT_STATUS_INITIALIZED,
9403 set_src);
9404 else
9405 var_mem_delete_and_set (set, loc, true, VAR_INIT_STATUS_INITIALIZED,
9406 set_src);
9408 emit_notes_for_changes (next_insn, EMIT_NOTE_BEFORE_INSN,
9409 set->vars);
9411 break;
9413 case MO_COPY:
9415 rtx loc = mo->u.loc;
9416 enum var_init_status src_status;
9417 rtx set_src = NULL;
9419 if (GET_CODE (loc) == SET)
9421 set_src = SET_SRC (loc);
9422 loc = SET_DEST (loc);
9425 src_status = find_src_status (set, set_src);
9426 set_src = find_src_set_src (set, set_src);
9428 if (REG_P (loc))
9429 var_reg_delete_and_set (set, loc, false, src_status, set_src);
9430 else
9431 var_mem_delete_and_set (set, loc, false, src_status, set_src);
9433 emit_notes_for_changes (next_insn, EMIT_NOTE_BEFORE_INSN,
9434 set->vars);
9436 break;
9438 case MO_USE_NO_VAR:
9440 rtx loc = mo->u.loc;
9442 if (REG_P (loc))
9443 var_reg_delete (set, loc, false);
9444 else
9445 var_mem_delete (set, loc, false);
9447 emit_notes_for_changes (insn, EMIT_NOTE_AFTER_INSN, set->vars);
9449 break;
9451 case MO_CLOBBER:
9453 rtx loc = mo->u.loc;
9455 if (REG_P (loc))
9456 var_reg_delete (set, loc, true);
9457 else
9458 var_mem_delete (set, loc, true);
9460 emit_notes_for_changes (next_insn, EMIT_NOTE_BEFORE_INSN,
9461 set->vars);
9463 break;
9465 case MO_ADJUST:
9466 set->stack_adjust += mo->u.adjust;
9467 break;
9472 /* Emit notes for the whole function. */
9474 static void
9475 vt_emit_notes (void)
9477 basic_block bb;
9478 dataflow_set cur;
9480 gcc_assert (!changed_variables->elements ());
9482 /* Free memory occupied by the out hash tables, as they aren't used
9483 anymore. */
9484 FOR_EACH_BB_FN (bb, cfun)
9485 dataflow_set_clear (&VTI (bb)->out);
9487 /* Enable emitting notes by functions (mainly by set_variable_part and
9488 delete_variable_part). */
9489 emit_notes = true;
9491 if (MAY_HAVE_DEBUG_INSNS)
9493 dropped_values = new variable_table_type (cselib_get_next_uid () * 2);
9496 dataflow_set_init (&cur);
9498 FOR_EACH_BB_FN (bb, cfun)
9500 /* Emit the notes for changes of variable locations between two
9501 subsequent basic blocks. */
9502 emit_notes_for_differences (BB_HEAD (bb), &cur, &VTI (bb)->in);
9504 if (MAY_HAVE_DEBUG_INSNS)
9505 local_get_addr_cache = new hash_map<rtx, rtx>;
9507 /* Emit the notes for the changes in the basic block itself. */
9508 emit_notes_in_bb (bb, &cur);
9510 if (MAY_HAVE_DEBUG_INSNS)
9511 delete local_get_addr_cache;
9512 local_get_addr_cache = NULL;
9514 /* Free memory occupied by the in hash table, we won't need it
9515 again. */
9516 dataflow_set_clear (&VTI (bb)->in);
9519 if (flag_checking)
9520 shared_hash_htab (cur.vars)
9521 ->traverse <variable_table_type *, emit_notes_for_differences_1>
9522 (shared_hash_htab (empty_shared_hash));
9524 dataflow_set_destroy (&cur);
9526 if (MAY_HAVE_DEBUG_INSNS)
9527 delete dropped_values;
9528 dropped_values = NULL;
9530 emit_notes = false;
9533 /* If there is a declaration and offset associated with register/memory RTL
9534 assign declaration to *DECLP and offset to *OFFSETP, and return true. */
9536 static bool
9537 vt_get_decl_and_offset (rtx rtl, tree *declp, HOST_WIDE_INT *offsetp)
9539 if (REG_P (rtl))
9541 if (REG_ATTRS (rtl))
9543 *declp = REG_EXPR (rtl);
9544 *offsetp = REG_OFFSET (rtl);
9545 return true;
9548 else if (GET_CODE (rtl) == PARALLEL)
9550 tree decl = NULL_TREE;
9551 HOST_WIDE_INT offset = MAX_VAR_PARTS;
9552 int len = XVECLEN (rtl, 0), i;
9554 for (i = 0; i < len; i++)
9556 rtx reg = XEXP (XVECEXP (rtl, 0, i), 0);
9557 if (!REG_P (reg) || !REG_ATTRS (reg))
9558 break;
9559 if (!decl)
9560 decl = REG_EXPR (reg);
9561 if (REG_EXPR (reg) != decl)
9562 break;
9563 if (REG_OFFSET (reg) < offset)
9564 offset = REG_OFFSET (reg);
9567 if (i == len)
9569 *declp = decl;
9570 *offsetp = offset;
9571 return true;
9574 else if (MEM_P (rtl))
9576 if (MEM_ATTRS (rtl))
9578 *declp = MEM_EXPR (rtl);
9579 *offsetp = INT_MEM_OFFSET (rtl);
9580 return true;
9583 return false;
9586 /* Record the value for the ENTRY_VALUE of RTL as a global equivalence
9587 of VAL. */
9589 static void
9590 record_entry_value (cselib_val *val, rtx rtl)
9592 rtx ev = gen_rtx_ENTRY_VALUE (GET_MODE (rtl));
9594 ENTRY_VALUE_EXP (ev) = rtl;
9596 cselib_add_permanent_equiv (val, ev, get_insns ());
9599 /* Insert function parameter PARM in IN and OUT sets of ENTRY_BLOCK. */
9601 static void
9602 vt_add_function_parameter (tree parm)
9604 rtx decl_rtl = DECL_RTL_IF_SET (parm);
9605 rtx incoming = DECL_INCOMING_RTL (parm);
9606 tree decl;
9607 machine_mode mode;
9608 HOST_WIDE_INT offset;
9609 dataflow_set *out;
9610 decl_or_value dv;
9612 if (TREE_CODE (parm) != PARM_DECL)
9613 return;
9615 if (!decl_rtl || !incoming)
9616 return;
9618 if (GET_MODE (decl_rtl) == BLKmode || GET_MODE (incoming) == BLKmode)
9619 return;
9621 /* If there is a DRAP register or a pseudo in internal_arg_pointer,
9622 rewrite the incoming location of parameters passed on the stack
9623 into MEMs based on the argument pointer, so that incoming doesn't
9624 depend on a pseudo. */
9625 if (MEM_P (incoming)
9626 && (XEXP (incoming, 0) == crtl->args.internal_arg_pointer
9627 || (GET_CODE (XEXP (incoming, 0)) == PLUS
9628 && XEXP (XEXP (incoming, 0), 0)
9629 == crtl->args.internal_arg_pointer
9630 && CONST_INT_P (XEXP (XEXP (incoming, 0), 1)))))
9632 HOST_WIDE_INT off = -FIRST_PARM_OFFSET (current_function_decl);
9633 if (GET_CODE (XEXP (incoming, 0)) == PLUS)
9634 off += INTVAL (XEXP (XEXP (incoming, 0), 1));
9635 incoming
9636 = replace_equiv_address_nv (incoming,
9637 plus_constant (Pmode,
9638 arg_pointer_rtx, off));
9641 #ifdef HAVE_window_save
9642 /* DECL_INCOMING_RTL uses the INCOMING_REGNO of parameter registers.
9643 If the target machine has an explicit window save instruction, the
9644 actual entry value is the corresponding OUTGOING_REGNO instead. */
9645 if (HAVE_window_save && !crtl->uses_only_leaf_regs)
9647 if (REG_P (incoming)
9648 && HARD_REGISTER_P (incoming)
9649 && OUTGOING_REGNO (REGNO (incoming)) != REGNO (incoming))
9651 parm_reg p;
9652 p.incoming = incoming;
9653 incoming
9654 = gen_rtx_REG_offset (incoming, GET_MODE (incoming),
9655 OUTGOING_REGNO (REGNO (incoming)), 0);
9656 p.outgoing = incoming;
9657 vec_safe_push (windowed_parm_regs, p);
9659 else if (GET_CODE (incoming) == PARALLEL)
9661 rtx outgoing
9662 = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (XVECLEN (incoming, 0)));
9663 int i;
9665 for (i = 0; i < XVECLEN (incoming, 0); i++)
9667 rtx reg = XEXP (XVECEXP (incoming, 0, i), 0);
9668 parm_reg p;
9669 p.incoming = reg;
9670 reg = gen_rtx_REG_offset (reg, GET_MODE (reg),
9671 OUTGOING_REGNO (REGNO (reg)), 0);
9672 p.outgoing = reg;
9673 XVECEXP (outgoing, 0, i)
9674 = gen_rtx_EXPR_LIST (VOIDmode, reg,
9675 XEXP (XVECEXP (incoming, 0, i), 1));
9676 vec_safe_push (windowed_parm_regs, p);
9679 incoming = outgoing;
9681 else if (MEM_P (incoming)
9682 && REG_P (XEXP (incoming, 0))
9683 && HARD_REGISTER_P (XEXP (incoming, 0)))
9685 rtx reg = XEXP (incoming, 0);
9686 if (OUTGOING_REGNO (REGNO (reg)) != REGNO (reg))
9688 parm_reg p;
9689 p.incoming = reg;
9690 reg = gen_raw_REG (GET_MODE (reg), OUTGOING_REGNO (REGNO (reg)));
9691 p.outgoing = reg;
9692 vec_safe_push (windowed_parm_regs, p);
9693 incoming = replace_equiv_address_nv (incoming, reg);
9697 #endif
9699 if (!vt_get_decl_and_offset (incoming, &decl, &offset))
9701 if (MEM_P (incoming))
9703 /* This means argument is passed by invisible reference. */
9704 offset = 0;
9705 decl = parm;
9707 else
9709 if (!vt_get_decl_and_offset (decl_rtl, &decl, &offset))
9710 return;
9711 offset += byte_lowpart_offset (GET_MODE (incoming),
9712 GET_MODE (decl_rtl));
9716 if (!decl)
9717 return;
9719 if (parm != decl)
9721 /* If that DECL_RTL wasn't a pseudo that got spilled to
9722 memory, bail out. Otherwise, the spill slot sharing code
9723 will force the memory to reference spill_slot_decl (%sfp),
9724 so we don't match above. That's ok, the pseudo must have
9725 referenced the entire parameter, so just reset OFFSET. */
9726 if (decl != get_spill_slot_decl (false))
9727 return;
9728 offset = 0;
9731 if (!track_loc_p (incoming, parm, offset, false, &mode, &offset))
9732 return;
9734 out = &VTI (ENTRY_BLOCK_PTR_FOR_FN (cfun))->out;
9736 dv = dv_from_decl (parm);
9738 if (target_for_debug_bind (parm)
9739 /* We can't deal with these right now, because this kind of
9740 variable is single-part. ??? We could handle parallels
9741 that describe multiple locations for the same single
9742 value, but ATM we don't. */
9743 && GET_CODE (incoming) != PARALLEL)
9745 cselib_val *val;
9746 rtx lowpart;
9748 /* ??? We shouldn't ever hit this, but it may happen because
9749 arguments passed by invisible reference aren't dealt with
9750 above: incoming-rtl will have Pmode rather than the
9751 expected mode for the type. */
9752 if (offset)
9753 return;
9755 lowpart = var_lowpart (mode, incoming);
9756 if (!lowpart)
9757 return;
9759 val = cselib_lookup_from_insn (lowpart, mode, true,
9760 VOIDmode, get_insns ());
9762 /* ??? Float-typed values in memory are not handled by
9763 cselib. */
9764 if (val)
9766 preserve_value (val);
9767 set_variable_part (out, val->val_rtx, dv, offset,
9768 VAR_INIT_STATUS_INITIALIZED, NULL, INSERT);
9769 dv = dv_from_value (val->val_rtx);
9772 if (MEM_P (incoming))
9774 val = cselib_lookup_from_insn (XEXP (incoming, 0), mode, true,
9775 VOIDmode, get_insns ());
9776 if (val)
9778 preserve_value (val);
9779 incoming = replace_equiv_address_nv (incoming, val->val_rtx);
9784 if (REG_P (incoming))
9786 incoming = var_lowpart (mode, incoming);
9787 gcc_assert (REGNO (incoming) < FIRST_PSEUDO_REGISTER);
9788 attrs_list_insert (&out->regs[REGNO (incoming)], dv, offset,
9789 incoming);
9790 set_variable_part (out, incoming, dv, offset,
9791 VAR_INIT_STATUS_INITIALIZED, NULL, INSERT);
9792 if (dv_is_value_p (dv))
9794 record_entry_value (CSELIB_VAL_PTR (dv_as_value (dv)), incoming);
9795 if (TREE_CODE (TREE_TYPE (parm)) == REFERENCE_TYPE
9796 && INTEGRAL_TYPE_P (TREE_TYPE (TREE_TYPE (parm))))
9798 machine_mode indmode
9799 = TYPE_MODE (TREE_TYPE (TREE_TYPE (parm)));
9800 rtx mem = gen_rtx_MEM (indmode, incoming);
9801 cselib_val *val = cselib_lookup_from_insn (mem, indmode, true,
9802 VOIDmode,
9803 get_insns ());
9804 if (val)
9806 preserve_value (val);
9807 record_entry_value (val, mem);
9808 set_variable_part (out, mem, dv_from_value (val->val_rtx), 0,
9809 VAR_INIT_STATUS_INITIALIZED, NULL, INSERT);
9814 else if (GET_CODE (incoming) == PARALLEL && !dv_onepart_p (dv))
9816 int i;
9818 for (i = 0; i < XVECLEN (incoming, 0); i++)
9820 rtx reg = XEXP (XVECEXP (incoming, 0, i), 0);
9821 offset = REG_OFFSET (reg);
9822 gcc_assert (REGNO (reg) < FIRST_PSEUDO_REGISTER);
9823 attrs_list_insert (&out->regs[REGNO (reg)], dv, offset, reg);
9824 set_variable_part (out, reg, dv, offset,
9825 VAR_INIT_STATUS_INITIALIZED, NULL, INSERT);
9828 else if (MEM_P (incoming))
9830 incoming = var_lowpart (mode, incoming);
9831 set_variable_part (out, incoming, dv, offset,
9832 VAR_INIT_STATUS_INITIALIZED, NULL, INSERT);
9836 /* Insert function parameters to IN and OUT sets of ENTRY_BLOCK. */
9838 static void
9839 vt_add_function_parameters (void)
9841 tree parm;
9843 for (parm = DECL_ARGUMENTS (current_function_decl);
9844 parm; parm = DECL_CHAIN (parm))
9845 if (!POINTER_BOUNDS_P (parm))
9846 vt_add_function_parameter (parm);
9848 if (DECL_HAS_VALUE_EXPR_P (DECL_RESULT (current_function_decl)))
9850 tree vexpr = DECL_VALUE_EXPR (DECL_RESULT (current_function_decl));
9852 if (TREE_CODE (vexpr) == INDIRECT_REF)
9853 vexpr = TREE_OPERAND (vexpr, 0);
9855 if (TREE_CODE (vexpr) == PARM_DECL
9856 && DECL_ARTIFICIAL (vexpr)
9857 && !DECL_IGNORED_P (vexpr)
9858 && DECL_NAMELESS (vexpr))
9859 vt_add_function_parameter (vexpr);
9863 /* Initialize cfa_base_rtx, create a preserved VALUE for it and
9864 ensure it isn't flushed during cselib_reset_table.
9865 Can be called only if frame_pointer_rtx resp. arg_pointer_rtx
9866 has been eliminated. */
9868 static void
9869 vt_init_cfa_base (void)
9871 cselib_val *val;
9873 #ifdef FRAME_POINTER_CFA_OFFSET
9874 cfa_base_rtx = frame_pointer_rtx;
9875 cfa_base_offset = -FRAME_POINTER_CFA_OFFSET (current_function_decl);
9876 #else
9877 cfa_base_rtx = arg_pointer_rtx;
9878 cfa_base_offset = -ARG_POINTER_CFA_OFFSET (current_function_decl);
9879 #endif
9880 if (cfa_base_rtx == hard_frame_pointer_rtx
9881 || !fixed_regs[REGNO (cfa_base_rtx)])
9883 cfa_base_rtx = NULL_RTX;
9884 return;
9886 if (!MAY_HAVE_DEBUG_INSNS)
9887 return;
9889 /* Tell alias analysis that cfa_base_rtx should share
9890 find_base_term value with stack pointer or hard frame pointer. */
9891 if (!frame_pointer_needed)
9892 vt_equate_reg_base_value (cfa_base_rtx, stack_pointer_rtx);
9893 else if (!crtl->stack_realign_tried)
9894 vt_equate_reg_base_value (cfa_base_rtx, hard_frame_pointer_rtx);
9896 val = cselib_lookup_from_insn (cfa_base_rtx, GET_MODE (cfa_base_rtx), 1,
9897 VOIDmode, get_insns ());
9898 preserve_value (val);
9899 cselib_preserve_cfa_base_value (val, REGNO (cfa_base_rtx));
9902 /* Allocate and initialize the data structures for variable tracking
9903 and parse the RTL to get the micro operations. */
9905 static bool
9906 vt_initialize (void)
9908 basic_block bb;
9909 HOST_WIDE_INT fp_cfa_offset = -1;
9911 alloc_aux_for_blocks (sizeof (variable_tracking_info));
9913 empty_shared_hash = shared_hash_pool.allocate ();
9914 empty_shared_hash->refcount = 1;
9915 empty_shared_hash->htab = new variable_table_type (1);
9916 changed_variables = new variable_table_type (10);
9918 /* Init the IN and OUT sets. */
9919 FOR_ALL_BB_FN (bb, cfun)
9921 VTI (bb)->visited = false;
9922 VTI (bb)->flooded = false;
9923 dataflow_set_init (&VTI (bb)->in);
9924 dataflow_set_init (&VTI (bb)->out);
9925 VTI (bb)->permp = NULL;
9928 if (MAY_HAVE_DEBUG_INSNS)
9930 cselib_init (CSELIB_RECORD_MEMORY | CSELIB_PRESERVE_CONSTANTS);
9931 scratch_regs = BITMAP_ALLOC (NULL);
9932 preserved_values.create (256);
9933 global_get_addr_cache = new hash_map<rtx, rtx>;
9935 else
9937 scratch_regs = NULL;
9938 global_get_addr_cache = NULL;
9941 if (MAY_HAVE_DEBUG_INSNS)
9943 rtx reg, expr;
9944 int ofst;
9945 cselib_val *val;
9947 #ifdef FRAME_POINTER_CFA_OFFSET
9948 reg = frame_pointer_rtx;
9949 ofst = FRAME_POINTER_CFA_OFFSET (current_function_decl);
9950 #else
9951 reg = arg_pointer_rtx;
9952 ofst = ARG_POINTER_CFA_OFFSET (current_function_decl);
9953 #endif
9955 ofst -= INCOMING_FRAME_SP_OFFSET;
9957 val = cselib_lookup_from_insn (reg, GET_MODE (reg), 1,
9958 VOIDmode, get_insns ());
9959 preserve_value (val);
9960 if (reg != hard_frame_pointer_rtx && fixed_regs[REGNO (reg)])
9961 cselib_preserve_cfa_base_value (val, REGNO (reg));
9962 expr = plus_constant (GET_MODE (stack_pointer_rtx),
9963 stack_pointer_rtx, -ofst);
9964 cselib_add_permanent_equiv (val, expr, get_insns ());
9966 if (ofst)
9968 val = cselib_lookup_from_insn (stack_pointer_rtx,
9969 GET_MODE (stack_pointer_rtx), 1,
9970 VOIDmode, get_insns ());
9971 preserve_value (val);
9972 expr = plus_constant (GET_MODE (reg), reg, ofst);
9973 cselib_add_permanent_equiv (val, expr, get_insns ());
9977 /* In order to factor out the adjustments made to the stack pointer or to
9978 the hard frame pointer and thus be able to use DW_OP_fbreg operations
9979 instead of individual location lists, we're going to rewrite MEMs based
9980 on them into MEMs based on the CFA by de-eliminating stack_pointer_rtx
9981 or hard_frame_pointer_rtx to the virtual CFA pointer frame_pointer_rtx
9982 resp. arg_pointer_rtx. We can do this either when there is no frame
9983 pointer in the function and stack adjustments are consistent for all
9984 basic blocks or when there is a frame pointer and no stack realignment.
9985 But we first have to check that frame_pointer_rtx resp. arg_pointer_rtx
9986 has been eliminated. */
9987 if (!frame_pointer_needed)
9989 rtx reg, elim;
9991 if (!vt_stack_adjustments ())
9992 return false;
9994 #ifdef FRAME_POINTER_CFA_OFFSET
9995 reg = frame_pointer_rtx;
9996 #else
9997 reg = arg_pointer_rtx;
9998 #endif
9999 elim = eliminate_regs (reg, VOIDmode, NULL_RTX);
10000 if (elim != reg)
10002 if (GET_CODE (elim) == PLUS)
10003 elim = XEXP (elim, 0);
10004 if (elim == stack_pointer_rtx)
10005 vt_init_cfa_base ();
10008 else if (!crtl->stack_realign_tried)
10010 rtx reg, elim;
10012 #ifdef FRAME_POINTER_CFA_OFFSET
10013 reg = frame_pointer_rtx;
10014 fp_cfa_offset = FRAME_POINTER_CFA_OFFSET (current_function_decl);
10015 #else
10016 reg = arg_pointer_rtx;
10017 fp_cfa_offset = ARG_POINTER_CFA_OFFSET (current_function_decl);
10018 #endif
10019 elim = eliminate_regs (reg, VOIDmode, NULL_RTX);
10020 if (elim != reg)
10022 if (GET_CODE (elim) == PLUS)
10024 fp_cfa_offset -= INTVAL (XEXP (elim, 1));
10025 elim = XEXP (elim, 0);
10027 if (elim != hard_frame_pointer_rtx)
10028 fp_cfa_offset = -1;
10030 else
10031 fp_cfa_offset = -1;
10034 /* If the stack is realigned and a DRAP register is used, we're going to
10035 rewrite MEMs based on it representing incoming locations of parameters
10036 passed on the stack into MEMs based on the argument pointer. Although
10037 we aren't going to rewrite other MEMs, we still need to initialize the
10038 virtual CFA pointer in order to ensure that the argument pointer will
10039 be seen as a constant throughout the function.
10041 ??? This doesn't work if FRAME_POINTER_CFA_OFFSET is defined. */
10042 else if (stack_realign_drap)
10044 rtx reg, elim;
10046 #ifdef FRAME_POINTER_CFA_OFFSET
10047 reg = frame_pointer_rtx;
10048 #else
10049 reg = arg_pointer_rtx;
10050 #endif
10051 elim = eliminate_regs (reg, VOIDmode, NULL_RTX);
10052 if (elim != reg)
10054 if (GET_CODE (elim) == PLUS)
10055 elim = XEXP (elim, 0);
10056 if (elim == hard_frame_pointer_rtx)
10057 vt_init_cfa_base ();
10061 hard_frame_pointer_adjustment = -1;
10063 vt_add_function_parameters ();
10065 FOR_EACH_BB_FN (bb, cfun)
10067 rtx_insn *insn;
10068 HOST_WIDE_INT pre, post = 0;
10069 basic_block first_bb, last_bb;
10071 if (MAY_HAVE_DEBUG_INSNS)
10073 cselib_record_sets_hook = add_with_sets;
10074 if (dump_file && (dump_flags & TDF_DETAILS))
10075 fprintf (dump_file, "first value: %i\n",
10076 cselib_get_next_uid ());
10079 first_bb = bb;
10080 for (;;)
10082 edge e;
10083 if (bb->next_bb == EXIT_BLOCK_PTR_FOR_FN (cfun)
10084 || ! single_pred_p (bb->next_bb))
10085 break;
10086 e = find_edge (bb, bb->next_bb);
10087 if (! e || (e->flags & EDGE_FALLTHRU) == 0)
10088 break;
10089 bb = bb->next_bb;
10091 last_bb = bb;
10093 /* Add the micro-operations to the vector. */
10094 FOR_BB_BETWEEN (bb, first_bb, last_bb->next_bb, next_bb)
10096 HOST_WIDE_INT offset = VTI (bb)->out.stack_adjust;
10097 VTI (bb)->out.stack_adjust = VTI (bb)->in.stack_adjust;
10098 for (insn = BB_HEAD (bb); insn != NEXT_INSN (BB_END (bb));
10099 insn = NEXT_INSN (insn))
10101 if (INSN_P (insn))
10103 if (!frame_pointer_needed)
10105 insn_stack_adjust_offset_pre_post (insn, &pre, &post);
10106 if (pre)
10108 micro_operation mo;
10109 mo.type = MO_ADJUST;
10110 mo.u.adjust = pre;
10111 mo.insn = insn;
10112 if (dump_file && (dump_flags & TDF_DETAILS))
10113 log_op_type (PATTERN (insn), bb, insn,
10114 MO_ADJUST, dump_file);
10115 VTI (bb)->mos.safe_push (mo);
10116 VTI (bb)->out.stack_adjust += pre;
10120 cselib_hook_called = false;
10121 adjust_insn (bb, insn);
10122 if (MAY_HAVE_DEBUG_INSNS)
10124 if (CALL_P (insn))
10125 prepare_call_arguments (bb, insn);
10126 cselib_process_insn (insn);
10127 if (dump_file && (dump_flags & TDF_DETAILS))
10129 print_rtl_single (dump_file, insn);
10130 dump_cselib_table (dump_file);
10133 if (!cselib_hook_called)
10134 add_with_sets (insn, 0, 0);
10135 cancel_changes (0);
10137 if (!frame_pointer_needed && post)
10139 micro_operation mo;
10140 mo.type = MO_ADJUST;
10141 mo.u.adjust = post;
10142 mo.insn = insn;
10143 if (dump_file && (dump_flags & TDF_DETAILS))
10144 log_op_type (PATTERN (insn), bb, insn,
10145 MO_ADJUST, dump_file);
10146 VTI (bb)->mos.safe_push (mo);
10147 VTI (bb)->out.stack_adjust += post;
10150 if (fp_cfa_offset != -1
10151 && hard_frame_pointer_adjustment == -1
10152 && fp_setter_insn (insn))
10154 vt_init_cfa_base ();
10155 hard_frame_pointer_adjustment = fp_cfa_offset;
10156 /* Disassociate sp from fp now. */
10157 if (MAY_HAVE_DEBUG_INSNS)
10159 cselib_val *v;
10160 cselib_invalidate_rtx (stack_pointer_rtx);
10161 v = cselib_lookup (stack_pointer_rtx, Pmode, 1,
10162 VOIDmode);
10163 if (v && !cselib_preserved_value_p (v))
10165 cselib_set_value_sp_based (v);
10166 preserve_value (v);
10172 gcc_assert (offset == VTI (bb)->out.stack_adjust);
10175 bb = last_bb;
10177 if (MAY_HAVE_DEBUG_INSNS)
10179 cselib_preserve_only_values ();
10180 cselib_reset_table (cselib_get_next_uid ());
10181 cselib_record_sets_hook = NULL;
10185 hard_frame_pointer_adjustment = -1;
10186 VTI (ENTRY_BLOCK_PTR_FOR_FN (cfun))->flooded = true;
10187 cfa_base_rtx = NULL_RTX;
10188 return true;
10191 /* This is *not* reset after each function. It gives each
10192 NOTE_INSN_DELETED_DEBUG_LABEL in the entire compilation
10193 a unique label number. */
10195 static int debug_label_num = 1;
10197 /* Get rid of all debug insns from the insn stream. */
10199 static void
10200 delete_debug_insns (void)
10202 basic_block bb;
10203 rtx_insn *insn, *next;
10205 if (!MAY_HAVE_DEBUG_INSNS)
10206 return;
10208 FOR_EACH_BB_FN (bb, cfun)
10210 FOR_BB_INSNS_SAFE (bb, insn, next)
10211 if (DEBUG_INSN_P (insn))
10213 tree decl = INSN_VAR_LOCATION_DECL (insn);
10214 if (TREE_CODE (decl) == LABEL_DECL
10215 && DECL_NAME (decl)
10216 && !DECL_RTL_SET_P (decl))
10218 PUT_CODE (insn, NOTE);
10219 NOTE_KIND (insn) = NOTE_INSN_DELETED_DEBUG_LABEL;
10220 NOTE_DELETED_LABEL_NAME (insn)
10221 = IDENTIFIER_POINTER (DECL_NAME (decl));
10222 SET_DECL_RTL (decl, insn);
10223 CODE_LABEL_NUMBER (insn) = debug_label_num++;
10225 else
10226 delete_insn (insn);
10231 /* Run a fast, BB-local only version of var tracking, to take care of
10232 information that we don't do global analysis on, such that not all
10233 information is lost. If SKIPPED holds, we're skipping the global
10234 pass entirely, so we should try to use information it would have
10235 handled as well.. */
10237 static void
10238 vt_debug_insns_local (bool skipped ATTRIBUTE_UNUSED)
10240 /* ??? Just skip it all for now. */
10241 delete_debug_insns ();
10244 /* Free the data structures needed for variable tracking. */
10246 static void
10247 vt_finalize (void)
10249 basic_block bb;
10251 FOR_EACH_BB_FN (bb, cfun)
10253 VTI (bb)->mos.release ();
10256 FOR_ALL_BB_FN (bb, cfun)
10258 dataflow_set_destroy (&VTI (bb)->in);
10259 dataflow_set_destroy (&VTI (bb)->out);
10260 if (VTI (bb)->permp)
10262 dataflow_set_destroy (VTI (bb)->permp);
10263 XDELETE (VTI (bb)->permp);
10266 free_aux_for_blocks ();
10267 delete empty_shared_hash->htab;
10268 empty_shared_hash->htab = NULL;
10269 delete changed_variables;
10270 changed_variables = NULL;
10271 attrs_pool.release ();
10272 var_pool.release ();
10273 location_chain_pool.release ();
10274 shared_hash_pool.release ();
10276 if (MAY_HAVE_DEBUG_INSNS)
10278 if (global_get_addr_cache)
10279 delete global_get_addr_cache;
10280 global_get_addr_cache = NULL;
10281 loc_exp_dep_pool.release ();
10282 valvar_pool.release ();
10283 preserved_values.release ();
10284 cselib_finish ();
10285 BITMAP_FREE (scratch_regs);
10286 scratch_regs = NULL;
10289 #ifdef HAVE_window_save
10290 vec_free (windowed_parm_regs);
10291 #endif
10293 if (vui_vec)
10294 XDELETEVEC (vui_vec);
10295 vui_vec = NULL;
10296 vui_allocated = 0;
10299 /* The entry point to variable tracking pass. */
10301 static inline unsigned int
10302 variable_tracking_main_1 (void)
10304 bool success;
10306 if (flag_var_tracking_assignments < 0
10307 /* Var-tracking right now assumes the IR doesn't contain
10308 any pseudos at this point. */
10309 || targetm.no_register_allocation)
10311 delete_debug_insns ();
10312 return 0;
10315 if (n_basic_blocks_for_fn (cfun) > 500 &&
10316 n_edges_for_fn (cfun) / n_basic_blocks_for_fn (cfun) >= 20)
10318 vt_debug_insns_local (true);
10319 return 0;
10322 mark_dfs_back_edges ();
10323 if (!vt_initialize ())
10325 vt_finalize ();
10326 vt_debug_insns_local (true);
10327 return 0;
10330 success = vt_find_locations ();
10332 if (!success && flag_var_tracking_assignments > 0)
10334 vt_finalize ();
10336 delete_debug_insns ();
10338 /* This is later restored by our caller. */
10339 flag_var_tracking_assignments = 0;
10341 success = vt_initialize ();
10342 gcc_assert (success);
10344 success = vt_find_locations ();
10347 if (!success)
10349 vt_finalize ();
10350 vt_debug_insns_local (false);
10351 return 0;
10354 if (dump_file && (dump_flags & TDF_DETAILS))
10356 dump_dataflow_sets ();
10357 dump_reg_info (dump_file);
10358 dump_flow_info (dump_file, dump_flags);
10361 timevar_push (TV_VAR_TRACKING_EMIT);
10362 vt_emit_notes ();
10363 timevar_pop (TV_VAR_TRACKING_EMIT);
10365 vt_finalize ();
10366 vt_debug_insns_local (false);
10367 return 0;
10370 unsigned int
10371 variable_tracking_main (void)
10373 unsigned int ret;
10374 int save = flag_var_tracking_assignments;
10376 ret = variable_tracking_main_1 ();
10378 flag_var_tracking_assignments = save;
10380 return ret;
10383 namespace {
10385 const pass_data pass_data_variable_tracking =
10387 RTL_PASS, /* type */
10388 "vartrack", /* name */
10389 OPTGROUP_NONE, /* optinfo_flags */
10390 TV_VAR_TRACKING, /* tv_id */
10391 0, /* properties_required */
10392 0, /* properties_provided */
10393 0, /* properties_destroyed */
10394 0, /* todo_flags_start */
10395 0, /* todo_flags_finish */
10398 class pass_variable_tracking : public rtl_opt_pass
10400 public:
10401 pass_variable_tracking (gcc::context *ctxt)
10402 : rtl_opt_pass (pass_data_variable_tracking, ctxt)
10405 /* opt_pass methods: */
10406 virtual bool gate (function *)
10408 return (flag_var_tracking && !targetm.delay_vartrack);
10411 virtual unsigned int execute (function *)
10413 return variable_tracking_main ();
10416 }; // class pass_variable_tracking
10418 } // anon namespace
10420 rtl_opt_pass *
10421 make_pass_variable_tracking (gcc::context *ctxt)
10423 return new pass_variable_tracking (ctxt);