diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 014b1366ecd7ea102b82f4102a4590716869f39b..5445bd5fd1fd0d1bf9b47333ef008dfe997445f5 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,11 @@
+2017-05-25  Marc Glisse  <marc.glisse@inria.fr>
+
+	* fold-const.c (fold_binary_loc) [(A & C) == D]: Remove transformation.
+	* match.pd (X == C): Rewrite it here.
+	(with_possible_nonzero_bits, with_possible_nonzero_bits2,
+	with_certain_nonzero_bits2): New predicates.
+	* tree-ssanames.c (get_nonzero_bits): Handle INTEGER_CST.
+
 2017-05-24  Nathan Sidwell  <nathan@acm.org>
 
 	* lto-streamer-in.c (lto_input_data_block): Adjust T const cast to
diff --git a/gcc/fold-const.c b/gcc/fold-const.c
index 736552c33a9af3876bfd01f3cf47a078dec6558b..efc0b1080593ccb13ae5564f736d99fe64ef30af 100644
--- a/gcc/fold-const.c
+++ b/gcc/fold-const.c
@@ -10636,24 +10636,6 @@ fold_binary_loc (location_t loc,
 	    }
 	}
 
-      /* If we have (A & C) == D where D & ~C != 0, convert this into 0.
-	 Similarly for NE_EXPR.  */
-      if (TREE_CODE (arg0) == BIT_AND_EXPR
-	  && TREE_CODE (arg1) == INTEGER_CST
-	  && TREE_CODE (TREE_OPERAND (arg0, 1)) == INTEGER_CST)
-	{
-	  tree notc = fold_build1_loc (loc, BIT_NOT_EXPR,
-				   TREE_TYPE (TREE_OPERAND (arg0, 1)),
-				   TREE_OPERAND (arg0, 1));
-	  tree dandnotc
-	    = fold_build2_loc (loc, BIT_AND_EXPR, TREE_TYPE (arg0),
-			       fold_convert_loc (loc, TREE_TYPE (arg0), arg1),
-			       notc);
-	  tree rslt = code == EQ_EXPR ? integer_zero_node : integer_one_node;
-	  if (integer_nonzerop (dandnotc))
-	    return omit_one_operand_loc (loc, type, rslt, arg0);
-	}
-
       /* If this is a comparison of a field, we may be able to simplify it.  */
       if ((TREE_CODE (arg0) == COMPONENT_REF
 	   || TREE_CODE (arg0) == BIT_FIELD_REF)
diff --git a/gcc/match.pd b/gcc/match.pd
index ba501498cdd7724621455b7cb4f1d4996020e2ae..618b2ec3da83c6a9a2bcbc91710825144482b8c3 100644
--- a/gcc/match.pd
+++ b/gcc/match.pd
@@ -1097,6 +1097,33 @@ DEFINE_INT_AND_FLOAT_ROUND_FN (RINT)
   (if (TREE_INT_CST_LOW (@1) & 1)
    { constant_boolean_node (cmp == NE_EXPR, type); })))
 
+/* Arguments on which one can call get_nonzero_bits to get the bits
+   possibly set.  */
+(match with_possible_nonzero_bits
+ INTEGER_CST@0)
+(match with_possible_nonzero_bits
+ SSA_NAME@0
+ (if (INTEGRAL_TYPE_P (TREE_TYPE (@0)) || POINTER_TYPE_P (TREE_TYPE (@0)))))
+/* Slightly extended version, do not make it recursive to keep it cheap.  */
+(match (with_possible_nonzero_bits2 @0)
+ with_possible_nonzero_bits@0)
+(match (with_possible_nonzero_bits2 @0)
+ (bit_and:c with_possible_nonzero_bits@0 @2))
+
+/* Same for bits that are known to be set, but we do not have
+   an equivalent to get_nonzero_bits yet.  */
+(match (with_certain_nonzero_bits2 @0)
+ INTEGER_CST@0)
+(match (with_certain_nonzero_bits2 @0)
+ (bit_ior @1 INTEGER_CST@0))
+
+/* X == C (or X & Z == Y | C) is impossible if ~nonzero(X) & C != 0.  */
+(for cmp (eq ne)
+ (simplify
+  (cmp:c (with_possible_nonzero_bits2 @0) (with_certain_nonzero_bits2 @1))
+  (if ((~get_nonzero_bits (@0) & @1) != 0)
+   { constant_boolean_node (cmp == NE_EXPR, type); })))
+
 /* ((X inner_op C0) outer_op C1)
    With X being a tree where value_range has reasoned certain bits to always be
    zero throughout its computed value range,
diff --git a/gcc/tree-ssanames.c b/gcc/tree-ssanames.c
index 353c7b1906a88ffa7f9d2a368e48209c22bb5c7c..e83dd469846b61c8b8e9e6d7556935545f368a21 100644
--- a/gcc/tree-ssanames.c
+++ b/gcc/tree-ssanames.c
@@ -427,11 +427,14 @@ set_nonzero_bits (tree name, const wide_int_ref &mask)
 }
 
 /* Return a widest_int with potentially non-zero bits in SSA_NAME
-   NAME, or -1 if unknown.  */
+   NAME, the constant for INTEGER_CST, or -1 if unknown.  */
 
 wide_int
 get_nonzero_bits (const_tree name)
 {
+  if (TREE_CODE (name) == INTEGER_CST)
+    return name;
+
   unsigned int precision = TYPE_PRECISION (TREE_TYPE (name));
   if (POINTER_TYPE_P (TREE_TYPE (name)))
     {