@@ -237,13 +237,7 @@ static struct llvm_tag {
237237 See comment before analyze_ret_info(). */
238238 LL_Type * return_ll_type ;
239239
240- LOGICAL no_debug_info ;
241- int last_sym_avail ;
242- int last_dtype_avail ;
243- DTYPE curr_ret_dtype ;
244240 char * buf ;
245- int buf_idx ;
246- int buf_sz ;
247241
248242 /** Map sptr -> OPERAND* for those formal function arguments that are saved
249243 to a local variable in the prolog by process_formal_arguments(). The
@@ -255,6 +249,15 @@ static struct llvm_tag {
255249 /** Map name -> func_type for intrinsics that have already been declared by
256250 get_intrinsic(). */
257251 hashmap_t declared_intrinsics ;
252+
253+ int last_sym_avail ;
254+ int last_dtype_avail ;
255+ int buf_idx ;
256+ int buf_sz ;
257+
258+ DTYPE curr_ret_dtype ;
259+
260+ unsigned no_debug_info : 1 ; /* set to emit engineering diagnostics */
258261} llvm_info ;
259262
260263typedef struct temp_buf {
@@ -5361,17 +5364,16 @@ remove_instr(INSTR_LIST *instr, LOGICAL update_usect_only)
53615364 return prev ;
53625365}
53635366
5364- static void
5367+ INLINE static void
53655368remove_dead_instrs (void )
53665369{
53675370 INSTR_LIST * instr ;
5368- instr = llvm_info .last_instr ;
5369- while (instr ) {
5370- if ((instr -> i_name == I_STORE ) && instr -> flags & DELETABLE )
5371+ for (instr = llvm_info .last_instr ; instr ;) {
5372+ if ((instr -> i_name == I_STORE ) && (instr -> flags & DELETABLE ))
53715373 instr = remove_instr (instr , FALSE);
5372- else if ((instr -> i_name != I_CALL && instr -> i_name != I_INVOKE &&
5373- instr -> i_name != I_ATOMICRMW ) &&
5374- (instr -> tmps != NULL ) && instr -> tmps -> use_count <= 0 )
5374+ else if ((instr -> i_name != I_CALL ) && ( instr -> i_name != I_INVOKE ) &&
5375+ ( instr -> i_name != I_ATOMICRMW ) && ( instr -> tmps != NULL ) &&
5376+ (instr -> tmps -> use_count <= 0 ) )
53755377 instr = remove_instr (instr , FALSE);
53765378 else
53775379 instr = instr -> prev ;
@@ -5413,7 +5415,33 @@ can_move_load_up_over_fence(INSTR_LIST *instr)
54135415 return true;
54145416}
54155417
5416- static OPERAND *
5418+ /**
5419+ \brief Clear DELETABLE flag from previous instructions
5420+ \param ilix The ILI of a LOAD instruction
5421+ */
5422+ void
5423+ clear_deletable_flags (int ilix )
5424+ {
5425+ INSTR_LIST * instr ;
5426+ int ld_nme ;
5427+
5428+ DEBUG_ASSERT (IL_TYPE (ILI_OPC (ilix )) == ILTY_LOAD , "must be load" );
5429+ ld_nme = ILI_OPND (ilix , 2 );
5430+ for (instr = llvm_info .last_instr ; instr ; instr = instr -> prev ) {
5431+ if (instr -> i_name == I_STORE ) {
5432+ if (instr -> ilix == 0 ) {
5433+ instr -> flags &= ~DELETABLE ;
5434+ continue ;
5435+ }
5436+ if (ld_nme == ILI_OPND (instr -> ilix , 3 )) {
5437+ instr -> flags &= ~DELETABLE ;
5438+ break ;
5439+ }
5440+ }
5441+ }
5442+ }
5443+
5444+ INLINE static OPERAND *
54175445find_load_cse (int ilix , OPERAND * load_op , LL_Type * llt )
54185446{
54195447 INSTR_LIST * instr , * del_store_instr , * last_instr ;
@@ -5462,11 +5490,10 @@ find_load_cse(int ilix, OPERAND *load_op, LL_Type *llt)
54625490 }
54635491
54645492 for (instr = llvm_info .last_instr ; instr != last_instr ; instr = instr -> prev ) {
5465- if (instr -> ilix == ilix ) {
5466- if (!same_op (instr -> operands , load_op ))
5467- return NULL ;
5468- return make_tmp_op (instr -> ll_type , instr -> tmps );
5469- }
5493+ if (instr -> ilix == ilix )
5494+ return same_op (instr -> operands , load_op )
5495+ ? make_tmp_op (instr -> ll_type , instr -> tmps ) : NULL ;
5496+
54705497 switch (instr -> i_name ) {
54715498 case I_LOAD :
54725499 case I_CMPXCHG :
0 commit comments