diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index cda150959898e6f3f39b9b132a8cfcc1c60c17f9..36ab804982880f99d7766845d79bcad7f8b6cd1a 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -41,6 +41,13 @@
 
 2010-04-12  Kaushik Phatak  <kaushik.phatak@kpitcummins.com>
 
+	* config/h8300/h8300.c (print_operand) : Modify case 'V' and
+	case 'W' print operands for HI mode.
+	* config/h8300/h8300.h (Y0, Y2) : New constraints.
+	* config/h8300/h8300.md (bclrqi_msx, bclrhi_msx): New patterns
+	(bsetqi_msx, bsethi_msx, bnotqi_msx, bnothi_msx): Likewise.
+	* config/h8300/predicate.md (bit_register_indirect_operand): New.
+
 	* config/h8300/h8300.h (OK_FOR_U): Support 'U' constraint for H8300SX.
 
 	* config/h8300/h8300.md (movqi_h8sx, movhi_h8sx, movsi_h8sx, 
diff --git a/gcc/config/h8300/h8300.c b/gcc/config/h8300/h8300.c
index ade1060cad9efaf7a631b7e84a0bc6804b2d8066..e53f3077a7e64fb715db9c30ab7c4686320c5116 100644
--- a/gcc/config/h8300/h8300.c
+++ b/gcc/config/h8300/h8300.c
@@ -1468,12 +1468,20 @@ print_operand (FILE *file, rtx x, int code)
 	goto def;
       break;
     case 'V':
-      bitint = exact_log2 (INTVAL (x) & 0xff);
+      bitint = (INTVAL (x) & 0xffff);
+      if ((exact_log2 ((bitint >> 8) & 0xff)) == -1)
+	bitint = exact_log2 (bitint & 0xff);
+      else
+        bitint = exact_log2 ((bitint >> 8) & 0xff);	      
       gcc_assert (bitint >= 0);
       fprintf (file, "#%d", bitint);
       break;
     case 'W':
-      bitint = exact_log2 ((~INTVAL (x)) & 0xff);
+      bitint = ((~INTVAL (x)) & 0xffff);
+      if ((exact_log2 ((bitint >> 8) & 0xff)) == -1 )
+	bitint = exact_log2 (bitint & 0xff);
+      else
+	bitint = (exact_log2 ((bitint >> 8) & 0xff));      
       gcc_assert (bitint >= 0);
       fprintf (file, "#%d", bitint);
       break;
diff --git a/gcc/config/h8300/h8300.h b/gcc/config/h8300/h8300.h
index d3f714c3afd064f3e62c5647226211d63f7c0fff..f77dfa31407c850af7ca6ca94f4a9672f17d8b07 100644
--- a/gcc/config/h8300/h8300.h
+++ b/gcc/config/h8300/h8300.h
@@ -819,15 +819,25 @@ struct cum_arg
   ((STR)[1] == 'U' ? 2					\
    : 0)
 
-/* We don't have any constraint starting with Y yet, but before
-   someone uses it for a one-letter constraint and we're left without
-   any upper-case constraints left, we reserve it for extensions
-   here.  */
-#define OK_FOR_Y(OP, STR)				\
-  (0)
+/* Multi-letter constraints starting with Y are to be used for operands
+   that are constant immediates and have single 1 or 0 in their binary
+   representation.  */
+
+#define OK_FOR_Y2(OP)                                   \
+  ((GET_CODE (OP) == CONST_INT) && (exact_log2 (INTVAL (OP) & 0xff) != -1))
+
+#define OK_FOR_Y0(OP)                                   \
+  ((GET_CODE (OP) == CONST_INT) && (exact_log2 (~INTVAL (OP) & 0xff) != -1))
+
+#define OK_FOR_Y(OP, STR)                               \
+  ((STR)[1] == '2' ? OK_FOR_Y2 (OP)                     \
+   : (STR)[1] == '0' ? OK_FOR_Y0 (OP)	\
+   : 0)
 
 #define CONSTRAINT_LEN_FOR_Y(STR)			\
-  (0)
+  ((STR)[1] == '2' ? 2                                  \
+   : (STR)[1] == '0' ? 2		\
+   : 0)
 
 #define OK_FOR_Z(OP)					\
   (TARGET_H8300SX					\
diff --git a/gcc/config/h8300/h8300.md b/gcc/config/h8300/h8300.md
index 289c33972ebd11c60941ad4647abfb3fd3f51d12..513ad4c3969a82c194d87d618e51e036064175a6 100644
--- a/gcc/config/h8300/h8300.md
+++ b/gcc/config/h8300/h8300.md
@@ -1762,7 +1762,34 @@
 ;; ----------------------------------------------------------------------
 ;; AND INSTRUCTIONS
 ;; ----------------------------------------------------------------------
+(define_insn "bclrqi_msx"
+  [(set (match_operand:QI 0 "bit_register_indirect_operand" "=WU")
+	(and:QI (match_operand:QI 1 "bit_register_indirect_operand" "%0")
+		(match_operand:QI 2 "single_zero_operand" "Y0")))]
+  "TARGET_H8300SX"
+  "bclr\\t%W2,%0"
+  [(set_attr "length" "8")])
+
+(define_split
+  [(set (match_operand:HI 0 "bit_register_indirect_operand" "=U")
+	(and:HI (match_operand:HI 1 "bit_register_indirect_operand" "%0")
+		(match_operand:HI 2 "single_zero_operand" "Y0")))]
+  "TARGET_H8300SX"
+  [(set (match_dup 0)
+	(and:QI (match_dup 1)
+		(match_dup 2)))]
+{
+  operands[0] = adjust_address (operands[0], QImode, 1);
+  operands[1] = adjust_address (operands[1], QImode, 1);
+})
 
+(define_insn "bclrhi_msx"
+  [(set (match_operand:HI 0 "bit_register_indirect_operand" "=m")
+	(and:HI (match_operand:HI 1 "bit_register_indirect_operand" "%0")
+		(match_operand:HI 2 "single_zero_operand" "Y0")))]
+  "TARGET_H8300SX"
+  "bclr\\t%W2,%0"
+  [(set_attr "length" "8")])
 (define_insn "*andqi3_2"
   [(set (match_operand:QI 0 "bit_operand" "=rQ,r")
 	(and:QI (match_operand:QI 1 "bit_operand" "%0,WU")
@@ -1866,6 +1893,34 @@
 ;; ----------------------------------------------------------------------
 ;; OR INSTRUCTIONS
 ;; ----------------------------------------------------------------------
+(define_insn "bsetqi_msx"
+  [(set (match_operand:QI 0 "bit_register_indirect_operand" "=WU")
+	(ior:QI (match_operand:QI 1 "bit_register_indirect_operand" "%0")
+		(match_operand:QI 2 "single_one_operand" "Y2")))]
+  "TARGET_H8300SX" 
+  "bset\\t%V2,%0"
+  [(set_attr "length" "8")])
+
+(define_split
+  [(set (match_operand:HI 0 "bit_register_indirect_operand" "=U")
+	(ior:HI (match_operand:HI 1 "bit_register_indirect_operand" "%0")
+		(match_operand:HI 2 "single_one_operand" "Y2")))]
+  "TARGET_H8300SX"
+  [(set (match_dup 0)
+	(ior:QI (match_dup 1)
+		(match_dup 2)))]
+{
+  operands[0] = adjust_address (operands[0], QImode, 1);
+  operands[1] = adjust_address (operands[1], QImode, 1);
+})
+
+(define_insn "bsethi_msx"
+  [(set (match_operand:HI 0 "bit_register_indirect_operand" "=m")
+	(ior:HI (match_operand:HI 1 "bit_register_indirect_operand" "%0")
+		(match_operand:HI 2 "single_one_operand" "Y2")))]
+  "TARGET_H8300SX"
+  "bset\\t%V2,%0"
+  [(set_attr "length" "8")])
 
 (define_insn "iorqi3_1"
   [(set (match_operand:QI 0 "bit_operand" "=rQ,U")
@@ -1904,6 +1959,34 @@
 ;; ----------------------------------------------------------------------
 ;; XOR INSTRUCTIONS
 ;; ----------------------------------------------------------------------
+(define_insn "bnotqi_msx"
+  [(set (match_operand:QI 0 "bit_register_indirect_operand" "=WU")
+	(xor:QI (match_operand:QI 1 "bit_register_indirect_operand" "%0")
+		(match_operand:QI 2 "single_one_operand" "Y2")))]
+  "TARGET_H8300SX"
+  "bnot\\t%V2,%0"
+  [(set_attr "length" "8")])
+
+(define_split
+  [(set (match_operand:HI 0 "bit_register_indirect_operand" "=U")
+	(xor:HI (match_operand:HI 1 "bit_register_indirect_operand" "%0")
+		(match_operand:HI 2 "single_one_operand" "Y2")))]
+  "TARGET_H8300SX"
+  [(set (match_dup 0)
+	(xor:QI (match_dup 1)
+		(match_dup 2)))]
+{
+  operands[0] = adjust_address (operands[0], QImode, 1);
+  operands[1] = adjust_address (operands[1], QImode, 1);
+})
+
+(define_insn "bnothi_msx"
+  [(set (match_operand:HI 0 "bit_register_indirect_operand" "=m")
+	(xor:HI (match_operand:HI 1 "bit_register_indirect_operand" "%0")
+		(match_operand:HI 2 "single_one_operand" "Y2")))]
+  "TARGET_H8300SX"
+  "bnot\\t%V2,%0"
+  [(set_attr "length" "8")])
 
 (define_insn "xorqi3_1"
   [(set (match_operand:QI 0 "bit_operand" "=r,U")
diff --git a/gcc/config/h8300/predicates.md b/gcc/config/h8300/predicates.md
index ea6c071acdde48d107daca7626b8ea4abe37d738..c4ea2d8cb754dd7bd4cf3b1eca5f5f9e0ea2b0cc 100644
--- a/gcc/config/h8300/predicates.md
+++ b/gcc/config/h8300/predicates.md
@@ -356,6 +356,17 @@
 	  && OK_FOR_U (op));
 })
 
+;; Return nonzero if OP is indirect register or constant memory
+;; suitable for bit manipulation insns.
+
+(define_predicate "bit_register_indirect_operand"
+  (match_code "mem")
+{
+  return (GET_CODE (op) == MEM
+          && (GET_CODE (XEXP (op, 0)) == REG
+              || GET_CODE (XEXP (op, 0)) == CONST_INT));
+})
+
 ;; Return nonzero if X is a stack pointer.
 
 (define_predicate "stack_pointer_operand"