--- /dev/null
+! { dg-do compile }
+! { dg-additional-options "-Ofast" }
+! { dg-additional-options "-mavx" { target x86_64-*-* i?86-*-* } }
+
+ SUBROUTINE PASSB4 (IDO,L1,CC,CH,WA1,WA2,WA3)
+ IMPLICIT REAL(4) (A-H, O-Z)
+ DIMENSION CC(IDO,4,L1) ,CH(IDO,L1,4) ,&
+ WA1(*) ,WA2(*) ,WA3(*)
+ 102 DO 104 K=1,L1
+ DO 103 I=2,IDO,2
+ TI1 = CC(I,1,K)-CC(I,3,K)
+ TI2 = CC(I,1,K)+CC(I,3,K)
+ TI3 = CC(I,2,K)+CC(I,4,K)
+ TR4 = CC(I,4,K)-CC(I,2,K)
+ TR1 = CC(I-1,1,K)-CC(I-1,3,K)
+ TR2 = CC(I-1,1,K)+CC(I-1,3,K)
+ TI4 = CC(I-1,2,K)-CC(I-1,4,K)
+ TR3 = CC(I-1,2,K)+CC(I-1,4,K)
+ CH(I-1,K,1) = TR2+TR3
+ CR3 = TR2-TR3
+ CH(I,K,1) = TI2+TI3
+ CI3 = TI2-TI3
+ CR2 = TR1+TR4
+ CI4 = TI1-TI4
+ CH(I-1,K,2) = TI1
+ CH(I,K,2) = CR2
+ CH(I-1,K,3) = WA2(I-1)*CR3-WA2(I)*CI3
+ CH(I,K,3) = WA2(I-1)*CI3+WA2(I)*CR3
+ CH(I-1,K,4) = CI4
+ CH(I,K,4) = CI4
+ 103 CONTINUE
+ 104 CONTINUE
+ RETURN
+ END
|| VECTORIZABLE_CYCLE_DEF (STMT_VINFO_DEF_TYPE (use_vinfo)))
&& !(gimple_code (use_stmt) == GIMPLE_PHI
&& STMT_VINFO_DEF_TYPE (use_vinfo) == vect_reduction_def))
- stype = hybrid;
+ {
+ if (dump_enabled_p ())
+ {
+ dump_printf_loc (MSG_NOTE, vect_location, "use of SLP "
+ "def in non-SLP stmt: ");
+ dump_gimple_stmt (MSG_NOTE, TDF_SLIM, use_stmt, 0);
+ }
+ stype = hybrid;
+ }
}
}
- if (stype == hybrid)
+ if (stype == hybrid
+ && !HYBRID_SLP_STMT (stmt_vinfo))
{
if (dump_enabled_p ())
{
the created stmts must be inserted. */
static inline void
-vect_create_mask_and_perm (gimple stmt, gimple next_scalar_stmt,
+vect_create_mask_and_perm (gimple stmt,
tree mask, int first_vec_indx, int second_vec_indx,
gimple_stmt_iterator *gsi, slp_tree node,
tree vectype, vec<tree> dr_chain,
{
tree perm_dest;
gimple perm_stmt = NULL;
- stmt_vec_info next_stmt_info;
int i, stride;
tree first_vec, second_vec, data_ref;
first_vec_indx += stride;
second_vec_indx += stride;
}
-
- /* Mark the scalar stmt as vectorized. */
- next_stmt_info = vinfo_for_stmt (next_scalar_stmt);
- STMT_VINFO_VEC_STMT (next_stmt_info) = perm_stmt;
}
gimple stmt = SLP_TREE_SCALAR_STMTS (node)[0];
stmt_vec_info stmt_info = vinfo_for_stmt (stmt);
tree mask_element_type = NULL_TREE, mask_type;
- int i, j, k, nunits, vec_index = 0, scalar_index;
+ int i, j, k, nunits, vec_index = 0;
tree vectype = STMT_VINFO_VECTYPE (stmt_info);
- gimple next_scalar_stmt;
int group_size = SLP_INSTANCE_GROUP_SIZE (slp_node_instance);
int first_mask_element;
int index, unroll_factor, current_mask_element, ncopies;
{c2,a3,b3,c3}. */
{
- scalar_index = 0;
index = 0;
vect_stmts_counter = 0;
vec_index = 0;
second_vec_index = vec_index;
}
- next_scalar_stmt
- = SLP_TREE_SCALAR_STMTS (node)[scalar_index++];
-
- vect_create_mask_and_perm (stmt, next_scalar_stmt,
+ vect_create_mask_and_perm (stmt,
mask_vec, first_vec_index, second_vec_index,
gsi, node, vectype, dr_chain,
ncopies, vect_stmts_counter++);