diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 8966e42a170ab7489d91ff9e61f21962c2154ff3..ceebe84fb2b950536bbe0bb18e84ba2db640d96f 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,10 @@
+2011-11-21  Georg-Johann Lay  <avr@gjlay.de>
+
+	* config/avr/avr.c (output_reload_in_const): Loading a byte with 0
+	must not affect cc0.
+	* config/avr/avr.md (*movhi, *movpsi, *movsi, *movsf): Zero to any
+	register does not change cc0. Same for any constant to ld-register.
+
 2011-11-21  Uros Bizjak  <ubizjak@gmail.com>
 
 	* config/i386/mmx.md (unspec) <UNSPEC_MOVNTQ, UNSPEC_PFRCP,
diff --git a/gcc/config/avr/avr.c b/gcc/config/avr/avr.c
index f9dd60388dfb548edc7489509331e4a90a85115b..543bb9c56c154d1b9b0c3da22e20a575cb54ffa1 100644
--- a/gcc/config/avr/avr.c
+++ b/gcc/config/avr/avr.c
@@ -8836,7 +8836,13 @@ avr_regno_mode_code_ok_for_base_p (int regno,
    LEN != NULL: set *LEN to the length of the instruction sequence
                 (in words) printed with LEN = NULL.
    If CLEAR_P is true, OP[0] had been cleard to Zero already.
-   If CLEAR_P is false, nothing is known about OP[0].  */
+   If CLEAR_P is false, nothing is known about OP[0].
+
+   The effect on cc0 is as follows:
+
+   Load 0 to any register          : NONE
+   Load ld register with any value : NONE
+   Anything else:                  : CLOBBER  */
 
 static void
 output_reload_in_const (rtx *op, rtx clobber_reg, int *len, bool clear_p)
@@ -8914,7 +8920,7 @@ output_reload_in_const (rtx *op, rtx clobber_reg, int *len, bool clear_p)
           xop[2] = clobber_reg;
 
           if (n >= 2 + (avr_current_arch->n_segments > 1))
-            avr_asm_len ("clr %0", xop, len, 1);
+            avr_asm_len ("mov %0,__zero_reg__", xop, len, 1);
           else
             avr_asm_len (asm_code[n][ldreg_p], xop, len, ldreg_p ? 1 : 2);
           continue;
@@ -8946,14 +8952,13 @@ output_reload_in_const (rtx *op, rtx clobber_reg, int *len, bool clear_p)
             }
         }
 
-      /* Use CLR to zero a value so that cc0 is set as expected
-         for zero.  */
+      /* Don't use CLR so that cc0 is set as expected.  */
       
       if (ival[n] == 0)
         {
           if (!clear_p)
-            avr_asm_len ("clr %0", &xdest[n], len, 1);
-          
+            avr_asm_len (ldreg_p ? "ldi %0,0" : "mov %0,__zero_reg__",
+                         &xdest[n], len, 1);
           continue;
         }
 
diff --git a/gcc/config/avr/avr.md b/gcc/config/avr/avr.md
index 67420ce9dabe6d1e5d25eace6ea1cf2a61de0d90..73632d880f78022792904562a931c33f886c9a47 100644
--- a/gcc/config/avr/avr.md
+++ b/gcc/config/avr/avr.md
@@ -649,7 +649,7 @@
   }
   [(set_attr "length" "2,2,6,7,2,6,5,2")
    (set_attr "adjust_len" "mov16")
-   (set_attr "cc" "none,clobber,clobber,clobber,none,clobber,none,none")])
+   (set_attr "cc" "none,none,clobber,clobber,none,clobber,none,none")])
 
 (define_peephole2 ; movw
   [(set (match_operand:QI 0 "even_register_operand" "")
@@ -752,7 +752,7 @@
   }
   [(set_attr "length" "3,3,8,9,4,10")
    (set_attr "adjust_len" "mov24")
-   (set_attr "cc" "none,set_zn,clobber,clobber,clobber,clobber")])
+   (set_attr "cc" "none,none,clobber,clobber,none,clobber")])
   
 ;;==========================================================================
 ;; move double word (32 bit)
@@ -793,7 +793,7 @@
   }
   [(set_attr "length" "4,4,8,9,4,10")
    (set_attr "adjust_len" "mov32")
-   (set_attr "cc" "none,set_zn,clobber,clobber,clobber,clobber")])
+   (set_attr "cc" "none,none,clobber,clobber,none,clobber")])
 
 ;; fffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff
 ;; move floating point numbers (32 bit)
@@ -809,7 +809,7 @@
   }
   [(set_attr "length" "4,4,8,9,4,10")
    (set_attr "adjust_len" "mov32")
-   (set_attr "cc" "none,set_zn,clobber,clobber,clobber,clobber")])
+   (set_attr "cc" "none,none,clobber,clobber,none,clobber")])
 
 (define_peephole2 ; *reload_insf
   [(match_scratch:QI 2 "d")