diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 64c670af0198ddf98eda8acee684e78f5e45b4a9..6a62f7ad7742033f572c9f0efcce8e1505f11f55 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,28 @@
+2010-10-06  Nicola Pero  <nicola.pero@meta-innovation.com>
+
+	Implemented fast enumeration for Objective-C.	
+	* c-parser.c (objc_could_be_foreach_context): New.
+	(c_lex_one_token): Recognize RID_IN keyword in a potential
+	Objective-C foreach context.
+	(c_parser_declaration_or_fndef): Added parameter.  Accept
+	Objective-C RID_IN keyword as terminating a declaration; in that
+	case, return the declaration in the new parameter.
+	(c_parser_extenral_declaration): Updated calls to
+	c_parser_declaration_or_fndef.
+	(c_parser_declaration_or_fndef): Same change.
+	(c_parser_compound_statement_nostart): Same change.
+	(c_parser_label): Same change.
+	(c_parser_objc_methodprotolist): Same change.
+	(c_parser_omp_for_loop): Same change.
+	(c_parser_for_statement): Detect and parse Objective-C foreach
+	statements.
+	(c_parser_omp_for_loop): Updated call to check_for_loop_decls().
+	* c-decl.c (check_for_loop_decls): Added parameter to allow ObjC
+	fast enumeration parsing code to turn off the c99 error but still
+	perform checks on the loop declarations.
+	* c-tree.h (check_for_loop_decls): Updated declaration.
+	* doc/objc.texi: Document fast enumeration.
+	
 2010-10-06  Nick Clifton  <nickc@redhat.com>
 
 	* config/mn10300/mn10300.h (FIRST_PSEUDO_REGISTER): Increment by
diff --git a/gcc/c-decl.c b/gcc/c-decl.c
index 91d853fd0387a70ef034d43f47ab710011bbfc17..acb00d46369b730555729e7d1c17eedee9d9d9a1 100644
--- a/gcc/c-decl.c
+++ b/gcc/c-decl.c
@@ -8310,16 +8310,23 @@ finish_function (void)
 
 /* Check the declarations given in a for-loop for satisfying the C99
    constraints.  If exactly one such decl is found, return it.  LOC is
-   the location of the opening parenthesis of the for loop.  */
+   the location of the opening parenthesis of the for loop.  The last
+   parameter allows you to control the "for loop initial declarations
+   are only allowed in C99 mode".  Normally, you should pass
+   flag_isoc99 as that parameter.  But in some cases (Objective-C
+   foreach loop, for example) we want to run the checks in this
+   function even if not in C99 mode, so we allow the caller to turn
+   off the error about not being in C99 mode.
+*/
 
 tree
-check_for_loop_decls (location_t loc)
+check_for_loop_decls (location_t loc, bool turn_off_iso_c99_error)
 {
   struct c_binding *b;
   tree one_decl = NULL_TREE;
   int n_decls = 0;
 
-  if (!flag_isoc99)
+  if (!turn_off_iso_c99_error)
     {
       static bool hint = true;
       /* If we get here, declarations have been used in a for loop without
diff --git a/gcc/c-family/ChangeLog b/gcc/c-family/ChangeLog
index efe6b54a984a17021063ea33b41da6d8ef04602b..c601968aac1049073d1cc2bc04d245e13fcb282f 100644
--- a/gcc/c-family/ChangeLog
+++ b/gcc/c-family/ChangeLog
@@ -1,3 +1,9 @@
+2010-10-06  Nicola Pero  <nicola.pero@meta-innovation.com>
+
+	Implemented fast enumeration for Objective-C.
+	* c-common.h (objc_finish_foreach_loop): New.
+	* stub-objc.c (objc_finish_foreach_loop): New.
+
 2010-10-05  Joseph Myers  <joseph@codesourcery.com>
 
 	* c-common.h (struct diagnostic_context): Don't declare here.
diff --git a/gcc/c-family/c-common.h b/gcc/c-family/c-common.h
index f8d7ff5291420cc4727f9a1369ff4b18c2341cbd..5c35465b1cb8d5dbd298f0b126d60360955c44c7 100644
--- a/gcc/c-family/c-common.h
+++ b/gcc/c-family/c-common.h
@@ -1007,6 +1007,7 @@ extern int objc_static_init_needed_p (void);
 extern tree objc_generate_static_init_call (tree);
 extern tree objc_generate_write_barrier (tree, enum tree_code, tree);
 extern void objc_set_method_opt (bool);
+extern void objc_finish_foreach_loop (location_t, tree, tree, tree, tree, tree);
 
 /* The following are provided by the C and C++ front-ends, and called by
    ObjC/ObjC++.  */
diff --git a/gcc/c-family/stub-objc.c b/gcc/c-family/stub-objc.c
index 3f88874619074925fe8486ec65ff970179fe88cd..52675840d9902b19c02abcbd437201cd7c3e053d 100644
--- a/gcc/c-family/stub-objc.c
+++ b/gcc/c-family/stub-objc.c
@@ -355,3 +355,11 @@ objc_generate_write_barrier (tree ARG_UNUSED (lhs),
 {
   return 0;
 }
+
+void
+objc_finish_foreach_loop (location_t ARG_UNUSED (location), tree ARG_UNUSED (object_expression),
+			  tree ARG_UNUSED (collection_expression), tree ARG_UNUSED (for_body),
+			  tree ARG_UNUSED (break_label), tree ARG_UNUSED (continue_label))
+{
+  return;
+}
diff --git a/gcc/c-parser.c b/gcc/c-parser.c
index 5b38a487f782cdebc315682e068b3b3c7320ce4c..eb7844853b7ac2fcadf541bb19ac7b7ef9387de0 100644
--- a/gcc/c-parser.c
+++ b/gcc/c-parser.c
@@ -185,6 +185,11 @@ typedef struct GTY(()) c_parser {
   /* True if we are in a context where the Objective-C "PQ" keywords
      are considered keywords.  */
   BOOL_BITFIELD objc_pq_context : 1;
+  /* True if we are parsing a (potential) Objective-C foreach
+     statement.  This is set to true after we parsed 'for (' and while
+     we wait for 'in' or ';' to decide if it's a standard C for loop or an
+     Objective-C foreach loop.  */
+  BOOL_BITFIELD objc_could_be_foreach_context : 1;
   /* The following flag is needed to contextualize Objective-C lexical
      analysis.  In some cases (e.g., 'int NSObject;'), it is
      undesirable to bind an identifier to an Objective-C class, even
@@ -253,6 +258,26 @@ c_lex_one_token (c_parser *parser, c_token *token)
 		    token->keyword = rid_code;
 		    break;
 		  }
+		else if (parser->objc_could_be_foreach_context
+			 && rid_code == RID_IN)
+		  {
+		    /* We are in Objective-C, inside a (potential)
+		       foreach context (which means after having
+		       parsed 'for (', but before having parsed ';'),
+		       and we found 'in'.  We consider it the keyword
+		       which terminates the declaration at the
+		       beginning of a foreach-statement.  Note that
+		       this means you can't use 'in' for anything else
+		       in that context; in particular, in Objective-C
+		       you can't use 'in' as the name of the running
+		       variable in a C for loop.  We could potentially
+		       try to add code here to disambiguate, but it
+		       seems a reasonable limitation.
+		    */
+		    token->type = CPP_KEYWORD;
+		    token->keyword = rid_code;
+		    break;
+		  }
 		/* Else, "pq" keywords outside of the "pq" context are
 		   not keywords, and we fall through to the code for
 		   normal tokens.
@@ -947,7 +972,7 @@ typedef enum c_dtr_syn {
 static void c_parser_external_declaration (c_parser *);
 static void c_parser_asm_definition (c_parser *);
 static void c_parser_declaration_or_fndef (c_parser *, bool, bool, bool,
-					   bool, bool);
+					   bool, bool, tree *);
 static void c_parser_static_assert_declaration_no_semi (c_parser *);
 static void c_parser_static_assert_declaration (c_parser *);
 static void c_parser_declspecs (c_parser *, struct c_declspecs *, bool, bool,
@@ -1170,7 +1195,7 @@ c_parser_external_declaration (c_parser *parser)
 	 an @interface or @protocol with prefix attributes).  We can
 	 only tell which after parsing the declaration specifiers, if
 	 any, and the first declarator.  */
-      c_parser_declaration_or_fndef (parser, true, true, true, false, true);
+      c_parser_declaration_or_fndef (parser, true, true, true, false, true, NULL);
       break;
     }
 }
@@ -1189,6 +1214,8 @@ c_parser_external_declaration (c_parser *parser)
    (old-style parameter declarations) they are diagnosed.  If
    START_ATTR_OK is true, the declaration specifiers may start with
    attributes; otherwise they may not.
+   OBJC_FOREACH_OBJECT_DECLARATION can be used to get back the parsed
+   declaration when parsing an Objective-C foreach statement.
 
    declaration:
      declaration-specifiers init-declarator-list[opt] ;
@@ -1235,6 +1262,10 @@ c_parser_external_declaration (c_parser *parser)
    specifiers, but only at top level (elsewhere they conflict with
    other syntax).
 
+   In Objective-C, declarations of the looping variable in a foreach
+   statement are exceptionally terminated by 'in' (for example, 'for
+   (NSObject *object in array) { ... }').
+
    OpenMP:
 
    declaration:
@@ -1243,7 +1274,8 @@ c_parser_external_declaration (c_parser *parser)
 static void
 c_parser_declaration_or_fndef (c_parser *parser, bool fndef_ok,
 			       bool static_assert_ok, bool empty_ok,
-			       bool nested, bool start_attr_ok)
+			       bool nested, bool start_attr_ok,
+			       tree *objc_foreach_object_declaration)
 {
   struct c_declspecs *specs;
   tree prefix_attrs;
@@ -1375,7 +1407,8 @@ c_parser_declaration_or_fndef (c_parser *parser, bool fndef_ok,
 	  || c_parser_next_token_is (parser, CPP_COMMA)
 	  || c_parser_next_token_is (parser, CPP_SEMICOLON)
 	  || c_parser_next_token_is_keyword (parser, RID_ASM)
-	  || c_parser_next_token_is_keyword (parser, RID_ATTRIBUTE))
+	  || c_parser_next_token_is_keyword (parser, RID_ATTRIBUTE)
+	  || c_parser_next_token_is_keyword (parser, RID_IN))
 	{
 	  tree asm_name = NULL_TREE;
 	  tree postfix_attrs = NULL_TREE;
@@ -1421,7 +1454,15 @@ c_parser_declaration_or_fndef (c_parser *parser, bool fndef_ok,
 					    all_prefix_attrs));
 	      if (d)
 		finish_decl (d, UNKNOWN_LOCATION, NULL_TREE,
-		    	     NULL_TREE, asm_name);
+			     NULL_TREE, asm_name);
+	      
+	      if (c_parser_next_token_is_keyword (parser, RID_IN))
+		{
+		  if (d)
+		    *objc_foreach_object_declaration = d;
+		  else
+		    *objc_foreach_object_declaration = error_mark_node;		    
+		}
 	    }
 	  if (c_parser_next_token_is (parser, CPP_COMMA))
 	    {
@@ -1438,6 +1479,15 @@ c_parser_declaration_or_fndef (c_parser *parser, bool fndef_ok,
 	      c_parser_consume_token (parser);
 	      return;
 	    }
+	  else if (c_parser_next_token_is_keyword (parser, RID_IN))
+	    {
+	      /* This can only happen in Objective-C: we found the
+		 'in' that terminates the declaration inside an
+		 Objective-C foreach statement.  Do not consume the
+		 token, so that the caller can use it to determine
+		 that this indeed is a foreach context.  */
+	      return;
+	    }
 	  else
 	    {
 	      c_parser_error (parser, "expected %<,%> or %<;%>");
@@ -1484,7 +1534,7 @@ c_parser_declaration_or_fndef (c_parser *parser, bool fndef_ok,
       while (c_parser_next_token_is_not (parser, CPP_EOF)
 	     && c_parser_next_token_is_not (parser, CPP_OPEN_BRACE))
 	c_parser_declaration_or_fndef (parser, false, false, false,
-				       true, false);
+				       true, false, NULL);
       store_parm_decls ();
       DECL_STRUCT_FUNCTION (current_function_decl)->function_start_locus
 	= c_parser_peek_token (parser)->location;
@@ -3743,7 +3793,7 @@ c_parser_compound_statement_nostart (c_parser *parser)
 	{
 	  last_label = false;
 	  mark_valid_location_for_stdc_pragma (false);
-	  c_parser_declaration_or_fndef (parser, true, true, true, true, true);
+	  c_parser_declaration_or_fndef (parser, true, true, true, true, true, NULL);
 	  if (last_stmt)
 	    pedwarn_c90 (loc,
 			 (pedantic && !flag_isoc99)
@@ -3771,7 +3821,7 @@ c_parser_compound_statement_nostart (c_parser *parser)
 	      last_label = false;
 	      mark_valid_location_for_stdc_pragma (false);
 	      c_parser_declaration_or_fndef (parser, true, true, true, true,
-					     true);
+					     true, NULL);
 	      /* Following the old parser, __extension__ does not
 		 disable this diagnostic.  */
 	      restore_extension_diagnostics (ext);
@@ -3911,7 +3961,7 @@ c_parser_label (c_parser *parser)
 	  c_parser_declaration_or_fndef (parser, /*fndef_ok*/ false,
 					 /*static_assert_ok*/ true,
 					 /*nested*/ true, /*empty_ok*/ false,
-					 /*start_attr_ok*/ true);
+					 /*start_attr_ok*/ true, NULL);
 	}
     }
 }
@@ -4427,20 +4477,68 @@ c_parser_do_statement (c_parser *parser)
    Note in particular that the nested function does not include a
    trailing ';', whereas the "declaration" production includes one.
    Also, can we reject bad declarations earlier and cheaper than
-   check_for_loop_decls?  */
+   check_for_loop_decls?
+
+   In Objective-C, there are two additional variants:
+
+   foreach-statement:
+     for ( expression in expresssion ) statement
+     for ( declaration in expression ) statement
+
+   This is inconsistent with C, because the second variant is allowed
+   even if c99 is not enabled.
+
+   The rest of the comment documents these Objective-C foreach-statement.
+
+   Here is the canonical example of the first variant:
+    for (object in array)    { do something with object }
+   we call the first expression ("object") the "object_expression" and 
+   the second expression ("array") the "collection_expression".
+   object_expression must be an lvalue of type "id" (a generic Objective-C
+   object) because the loop works by assigning to object_expression the
+   various objects from the collection_expression.  collection_expression
+   must evaluate to something of type "id" which responds to the method
+   countByEnumeratingWithState:objects:count:.
+
+   The canonical example of the second variant is:
+    for (id object in array)    { do something with object }
+   which is completely equivalent to
+    {
+      id object;
+      for (object in array) { do something with object }
+    }
+   Note that initizializing 'object' in some way (eg, "for ((object =
+   xxx) in array) { do something with object }") is possibly
+   technically valid, but completely pointless as 'object' will be
+   assigned to something else as soon as the loop starts.  We should
+   most likely reject it (TODO).
+
+   The beginning of the Objective-C foreach-statement looks exactly
+   like the beginning of the for-statement, and we can tell it is a
+   foreach-statement only because the initial declaration or
+   expression is terminated by 'in' instead of ';'.
+*/
 
 static void
 c_parser_for_statement (c_parser *parser)
 {
   tree block, cond, incr, save_break, save_cont, body;
+  /* The following are only used when parsing an ObjC foreach statement.  */
+  tree object_expression, collection_expression;
   location_t loc = c_parser_peek_token (parser)->location;
   location_t for_loc = c_parser_peek_token (parser)->location;
+  bool is_foreach_statement = false;
   gcc_assert (c_parser_next_token_is_keyword (parser, RID_FOR));
   c_parser_consume_token (parser);
-  block = c_begin_compound_stmt (flag_isoc99);
+  /* Open a compound statement in Objective-C as well, just in case this is
+     as foreach expression.  */
+  block = c_begin_compound_stmt (flag_isoc99 || c_dialect_objc ());
   if (c_parser_require (parser, CPP_OPEN_PAREN, "expected %<(%>"))
     {
       /* Parse the initialization declaration or expression.  */
+      cond = error_mark_node;
+      object_expression = error_mark_node;
+
       if (c_parser_next_token_is (parser, CPP_SEMICOLON))
 	{
 	  c_parser_consume_token (parser);
@@ -4448,8 +4546,20 @@ c_parser_for_statement (c_parser *parser)
 	}
       else if (c_parser_next_token_starts_declaration (parser))
 	{
-	  c_parser_declaration_or_fndef (parser, true, true, true, true, true);
-	  check_for_loop_decls (for_loc);
+	  parser->objc_could_be_foreach_context = true;
+	  c_parser_declaration_or_fndef (parser, true, true, true, true, true, 
+					 &object_expression);
+	  parser->objc_could_be_foreach_context = false;
+	  
+	  if (c_parser_next_token_is_keyword (parser, RID_IN))
+	    {
+	      c_parser_consume_token (parser);
+	      is_foreach_statement = true;
+	      if (check_for_loop_decls (for_loc, true) == NULL_TREE)
+		c_parser_error (parser, "multiple iterating variables in fast enumeration");
+	    }
+	  else
+	    check_for_loop_decls (for_loc, flag_isoc99);
 	}
       else if (c_parser_next_token_is_keyword (parser, RID_EXTENSION))
 	{
@@ -4466,10 +4576,21 @@ c_parser_for_statement (c_parser *parser)
 	      int ext;
 	      ext = disable_extension_diagnostics ();
 	      c_parser_consume_token (parser);
+	      parser->objc_could_be_foreach_context = true;
 	      c_parser_declaration_or_fndef (parser, true, true, true, true,
-					     true);
+					     true, &object_expression);
+	      parser->objc_could_be_foreach_context = false;
+	      
 	      restore_extension_diagnostics (ext);
-	      check_for_loop_decls (for_loc);
+	      if (c_parser_next_token_is_keyword (parser, RID_IN))
+		{
+		  c_parser_consume_token (parser);
+		  is_foreach_statement = true;
+		  if (check_for_loop_decls (for_loc, true) == NULL_TREE)
+		    c_parser_error (parser, "multiple iterating variables in fast enumeration");
+		}
+	      else
+		check_for_loop_decls (for_loc, flag_isoc99);
 	    }
 	  else
 	    goto init_expr;
@@ -4477,25 +4598,62 @@ c_parser_for_statement (c_parser *parser)
       else
 	{
 	init_expr:
-	  c_finish_expr_stmt (loc, c_parser_expression (parser).value);
-	  c_parser_skip_until_found (parser, CPP_SEMICOLON, "expected %<;%>");
+	  {
+	    tree init_expression;
+	    parser->objc_could_be_foreach_context = true;
+	    init_expression = c_parser_expression (parser).value;
+	    parser->objc_could_be_foreach_context = false;
+	    if (c_parser_next_token_is_keyword (parser, RID_IN))
+	      {
+		c_parser_consume_token (parser);
+		is_foreach_statement = true;
+		if (! lvalue_p (init_expression))
+		  c_parser_error (parser, "invalid iterating variable in fast enumeration");
+		object_expression = c_process_expr_stmt (loc, init_expression);
+
+	      }
+	    else
+	      {
+		c_finish_expr_stmt (loc, init_expression);
+		c_parser_skip_until_found (parser, CPP_SEMICOLON, "expected %<;%>");
+	      }
+	  }
 	}
-      /* Parse the loop condition.  */
-      if (c_parser_next_token_is (parser, CPP_SEMICOLON))
+      /* Parse the loop condition.  In the case of a foreach
+	 statement, there is no loop condition.  */
+      if (!is_foreach_statement)
 	{
-	  c_parser_consume_token (parser);
-	  cond = NULL_TREE;
+	  if (c_parser_next_token_is (parser, CPP_SEMICOLON))
+	    {
+	      c_parser_consume_token (parser);
+	      cond = NULL_TREE;
+	    }
+	  else
+	    {
+	      cond = c_parser_condition (parser);
+	      c_parser_skip_until_found (parser, CPP_SEMICOLON, "expected %<;%>");
+	    }
 	}
-      else
+      /* Parse the increment expression (the third expression in a
+	 for-statement).  In the case of a foreach-statement, this is
+	 the expression that follows the 'in'.  */
+      if (c_parser_next_token_is (parser, CPP_CLOSE_PAREN))
 	{
-	  cond = c_parser_condition (parser);
-	  c_parser_skip_until_found (parser, CPP_SEMICOLON, "expected %<;%>");
+	  if (is_foreach_statement)
+	    {
+	      c_parser_error (parser, "missing collection in fast enumeration");
+	      collection_expression = error_mark_node;
+	    }
+	  else
+	    incr = c_process_expr_stmt (loc, NULL_TREE);
 	}
-      /* Parse the increment expression.  */
-      if (c_parser_next_token_is (parser, CPP_CLOSE_PAREN))
-	incr = c_process_expr_stmt (loc, NULL_TREE);
       else
-	incr = c_process_expr_stmt (loc, c_parser_expression (parser).value);
+	{
+	  if (is_foreach_statement)
+	    collection_expression = c_process_expr_stmt (loc, c_parser_expression (parser).value);
+	  else
+	    incr = c_process_expr_stmt (loc, c_parser_expression (parser).value);
+	}
       c_parser_skip_until_found (parser, CPP_CLOSE_PAREN, "expected %<)%>");
     }
   else
@@ -4508,8 +4666,11 @@ c_parser_for_statement (c_parser *parser)
   save_cont = c_cont_label;
   c_cont_label = NULL_TREE;
   body = c_parser_c99_block_statement (parser);
-  c_finish_loop (loc, cond, incr, body, c_break_label, c_cont_label, true);
-  add_stmt (c_end_compound_stmt (loc, block, flag_isoc99));
+  if (is_foreach_statement)
+    objc_finish_foreach_loop (loc, object_expression, collection_expression, body, c_break_label, c_cont_label);
+  else
+    c_finish_loop (loc, cond, incr, body, c_break_label, c_cont_label, true);
+  add_stmt (c_end_compound_stmt (loc, block, flag_isoc99 || c_dialect_objc ()));
   c_break_label = save_break;
   c_cont_label = save_cont;
 }
@@ -6790,7 +6951,7 @@ c_parser_objc_methodprotolist (c_parser *parser)
 	    }
 	  else
 	    c_parser_declaration_or_fndef (parser, false, false, true,
-					 false, true);
+					   false, true, NULL);
 	  break;
 	}
     }
@@ -8439,8 +8600,8 @@ c_parser_omp_for_loop (location_t loc,
 	{
 	  if (i > 0)
 	    VEC_safe_push (tree, gc, for_block, c_begin_compound_stmt (true));
-	  c_parser_declaration_or_fndef (parser, true, true, true, true, true);
-	  decl = check_for_loop_decls (for_loc);
+	  c_parser_declaration_or_fndef (parser, true, true, true, true, true, NULL);
+	  decl = check_for_loop_decls (for_loc, flag_isoc99);
 	  if (decl == NULL)
 	    goto error_init;
 	  if (DECL_INITIAL (decl) == error_mark_node)
diff --git a/gcc/c-tree.h b/gcc/c-tree.h
index ff349e3723a9666101b3a8d0dfcc99b4b5a43190..0d94cebd84d15559b67c64c2822c1587c65f3bb9 100644
--- a/gcc/c-tree.h
+++ b/gcc/c-tree.h
@@ -429,7 +429,7 @@ extern struct c_declarator *build_array_declarator (location_t, tree,
 						    bool, bool);
 extern tree build_enumerator (location_t, location_t, struct c_enum_contents *,
 			      tree, tree);
-extern tree check_for_loop_decls (location_t);
+extern tree check_for_loop_decls (location_t, bool);
 extern void mark_forward_parm_decls (void);
 extern void declare_parm_level (void);
 extern void undeclared_variable (location_t, tree);
diff --git a/gcc/doc/objc.texi b/gcc/doc/objc.texi
index bf328797c72678121e987bf04a3d38ef32735f44..2bb80d15254e9778e0151a91d737476198b300e2 100644
--- a/gcc/doc/objc.texi
+++ b/gcc/doc/objc.texi
@@ -20,6 +20,7 @@ several resources on the Internet that present the language.
 * compatibility_alias::
 * Exceptions::
 * Synchronization::
+* Fast enumeration::
 @end menu
 
 @node Executing code before main
@@ -739,3 +740,218 @@ Because of the interactions between synchronization and exception
 handling, you can only use @code{@@synchronized} when compiling with
 exceptions enabled, that is with the command line option
 @option{-fobjc-exceptions}.
+
+
+@c =========================================================================
+@node Fast enumeration
+@section Fast enumeration
+
+@menu
+* Using fast enumeration::
+* c99-like fast enumeration syntax::
+* Fast enumeration details::
+* Fast enumeration protocol::
+@end menu
+
+@c ================================
+@node Using fast enumeration
+@subsection Using fast enumeration
+
+GNU Objective-C provides support for the fast enumeration syntax:
+
+@smallexample
+  id array = @dots{};
+  id object;
+
+  for (object in array)
+  @{
+    /* Do something with 'object' */
+  @}
+@end smallexample
+
+@code{array} needs to be an Objective-C object (usually a collection
+object, for example an array, a dictionary or a set) which implements
+the ``Fast Enumeration Protocol'' (see below).  If you are using a
+Foundation library such as GNUstep Base or Apple Cocoa Foundation, all
+collection objects in the library implement this protocol and can be
+used in this way.
+
+The code above would iterate over all objects in @code{array}.  For
+each of them, it assigns it to @code{object}, then executes the
+@code{Do something with 'object'} statements.
+
+Here is a fully worked-out example using a Foundation library (which
+provides the implementation of @code{NSArray}, @code{NSString} and
+@code{NSLog}):
+
+@smallexample
+  NSArray *array = [NSArray arrayWithObjects: @@"1", @@"2", @@"3", nil];
+  NSString *object;
+
+  for (object in array)
+    NSLog (@@"Iterating over %@@", object);
+@end smallexample
+
+
+@c ================================
+@node c99-like fast enumeration syntax
+@subsection c99-like fast enumeration syntax
+
+A c99-like declaration syntax is also allowed:
+
+@smallexample
+  id array = @dots{};
+
+  for (id object in array)
+  @{
+    /* Do something with 'object'  */
+  @}
+@end smallexample
+
+this is completely equivalent to:
+
+@smallexample
+  id array = @dots{};
+
+  @{
+    id object;
+    for (object in array)
+    @{
+      /* Do something with 'object'  */
+    @}
+  @}
+@end smallexample
+
+but can save some typing.
+
+Note that the option @option{-std=c99} is not required to allow this
+syntax in Objective-C.
+
+@c ================================
+@node Fast enumeration details
+@subsection Fast enumeration details
+
+Here is a more technical description with the gory details.  Consider the code
+
+@smallexample
+  for (@var{object expression} in @var{collection expression})
+  @{
+    @var{statements}
+  @}
+@end smallexample
+
+here is what happens when you run it:
+
+@itemize @bullet
+@item
+@code{@var{collection expression}} is evaluated exactly once and the
+result is used as the collection object to iterate over.  This means
+it is safe to write code such as @code{for (object in [NSDictionary
+keyEnumerator]) @dots{}}.
+
+@item
+the iteration is implemented by the compiler by repeatedly getting
+batches of objects from the collection object using the fast
+enumeration protocol (see below), then iterating over all objects in
+the batch.  This is faster than a normal enumeration where objects are
+retrieved one by one (hence the name ``fast enumeration'').
+
+@item
+if there are no objects in the collection, then
+@code{@var{object expression}} is set to @code{nil} and the loop
+immediately terminates.
+
+@item
+if there are objects in the collection, then for each object in the
+collection (in the order they are returned) @code{@var{object expression}}
+is set to the object, then @code{@var{statements}} are executed.
+
+@item
+@code{@var{statements}} can contain @code{break} and @code{continue}
+commands, which will abort the iteration or skip to the next loop
+iteration as expected.
+
+@item
+when the iteration ends because there are no more objects to iterate
+over, @code{@var{object expression}} is set to @code{nil}.  This allows
+you to determine whether the iteration finished because a @code{break}
+command was used (in which case @code{@var{object expression}} will remain
+set to the last object that was iterated over) or because it iterated
+over all the objects (in which case @code{@var{object expression}} will be
+set to @code{nil}).
+
+@item
+@code{@var{statements}} must not make any changes to the collection
+object; if they do, it is a hard error and the fast enumeration
+terminates by invoking @code{objc_enumerationMutation}, a runtime
+function that normally aborts the program but which can be customized
+by Foundation libraries via @code{objc_set_mutation_handler} to do
+something different, such as raising an exception.
+
+@end itemize
+
+@c ================================
+@node Fast enumeration protocol
+@subsection Fast enumeration protocol
+
+If you want your own collection object to be usable with fast
+enumeration, you need to have it implement the method
+
+@smallexample
+- (unsigned long) countByEnumeratingWithState: (NSFastEnumerationState *)state 
+                                      objects: (id *)objects
+                                        count: (unsigneld long)len;
+@end smallexample
+
+where @code{NSFastEnumerationState} must be defined in your code as follows:
+
+@smallexample
+typdef struct
+@{
+  unsigned long state;
+  id            *itemsPtr;
+  unsigned long *mutationsPtr;
+  unsigned long extra[5];
+@} NSFastEnumerationState;
+@end smallexample
+
+If no @code{NSFastEnumerationState} is defined in your code, the
+compiler will automatically replace @code{NSFastEnumerationState *}
+with @code{struct __objcFastEnumerationState *}, where that type is
+silently defined by the compiler in an identical way.  This can be
+confusing and we recommend that you define
+@code{NSFastEnumerationState} (as shown above) instead.
+
+The method is called repeatedly during a fast enumeration to retrieve
+batches of objects.  Each invocation of the method should retrieve the
+next batch of objects.
+
+The return value of the method is the number of objects in the current
+batch; this should not exceed @code{len}, which is the maximum size of
+a batch as requested by the caller.  The batch itself is returned in
+the @code{itemsPtr} field of the @code{NSFastEnumerationState} struct.
+
+To help with returning the objects, the @code{objects} array is a C
+array preallocated by the caller (on the stack) of size @code{len}.
+In many cases you can put the objects you want to return in that
+@code{objects} array, then do @code{itemsPtr = objects}.  But you
+don't have to; if your collection already has the objects to return in
+some form of C array, it could return them from there instead.
+
+The @code{state} and @code{extra} fields of the
+@code{NSFastEnumerationState} structure allows your collection object
+to keep track of the state of the enumeration.  In a simple array
+implementation, @code{state} may keep track of the index of the last
+object that was returned, and @code{extra} may be unused.
+
+The @code{mutationsPtr} field of the @code{NSFastEnumerationState} is
+used to keep track of mutations.  It should point to a number; before
+working on each object, the fast enumeration loop will check that this
+number has not changed.  If it has, a mutation has happened and the
+fast enumeration will abort.  So, @code{mutationsPtr} could be set to
+point to some sort of version number of your collection, which is
+increased by one every time there is a change (for example when an
+object is added or removed).  Or, if you are content with less strict
+mutation checks, it could point to the number of objects in your
+collection or some other value that can be checked to perform an
+approximate check that the collection has not been mutated.
diff --git a/gcc/objc/ChangeLog b/gcc/objc/ChangeLog
index a68b46d71e760532642793046f8ddab9826e9ef5..eed86bd4a0659e6c9ea23ae7229d27c5b15760d0 100644
--- a/gcc/objc/ChangeLog
+++ b/gcc/objc/ChangeLog
@@ -1,3 +1,31 @@
+2010-10-06  Nicola Pero  <nicola.pero@meta-innovation.com>
+
+	Implemented fast enumeration for Objective-C.
+	* objc-act.c (build_fast_enumeration_state_template): New.
+	(TAG_ENUMERATION_MUTATION): New.
+	(TAG_FAST_ENUMERATION_STATE): New.
+	(synth_module_prologue): Call build_fast_enumeration_state_template() and set up
+	objc_enumeration_mutation_decl.
+	(objc_create_temporary_var): Allow providing a name to temporary
+	variables.
+	(objc_build_exc_ptr): Updated calls to
+	objc_create_temporary_var().
+	(next_sjlj_build_try_catch_finally): Same change.
+	(objc_finish_foreach_loop): New.
+	* objc-act.h: Added OCTI_FAST_ENUM_STATE_TEMP,
+	OCTI_ENUM_MUTATION_DECL, objc_fast_enumeration_state_template,
+	objc_enumeration_mutation_decl.
+
+	Merge from 'apple/trunk' branch on FSF servers.
+
+	2006-04-12 Fariborz Jahanian <fjahanian@apple.com>
+
+        Radar 4507230
+	* objc-act.c (objc_type_valid_for_messaging): New routine to check
+	for valid objc object types.
+	(objc_finish_foreach_loop): Check for invalid objc objects in
+	foreach header.
+	
 2010-10-05  Nicola Pero  <nicola.pero@meta-innovation.com>
 
 	Merge from 'apple/trunk' branch on FSF servers.
@@ -5,8 +33,8 @@
 	2005-10-17  Fariborz Jahanian <fjahanian@apple.com>
 
         Radar 4290840
-	* objc-act.c (objc_start_method_definition): Check for error_mark_node for
-	the selector name and make a quick exit.
+	* objc-act.c (objc_start_method_definition): Check for
+	error_mark_node for the selector name and make a quick exit.
 	
 2010-10-04  Andi Kleen <ak@linux.intel.com>
 
diff --git a/gcc/objc/objc-act.c b/gcc/objc/objc-act.c
index 5aaadc67ceb7cacbf4a39da341a4e6eb80dca93e..730efba48d832c832277780f6203b4c362a6cc3b 100644
--- a/gcc/objc/objc-act.c
+++ b/gcc/objc/objc-act.c
@@ -171,6 +171,8 @@ static tree get_class_ivars (tree, bool);
 static tree generate_protocol_list (tree);
 static void build_protocol_reference (tree);
 
+static void build_fast_enumeration_state_template (void);
+
 #ifdef OBJCPLUS
 static void objc_generate_cxx_cdtors (void);
 #endif
@@ -240,6 +242,7 @@ static void generate_struct_by_value_array (void)
      ATTRIBUTE_NORETURN;
 static void mark_referenced_methods (void);
 static void generate_objc_image_info (void);
+static bool objc_type_valid_for_messaging (tree typ);
 
 /*** Private Interface (data) ***/
 
@@ -274,6 +277,9 @@ static void generate_objc_image_info (void);
 
 #define PROTOCOL_OBJECT_CLASS_NAME	"Protocol"
 
+#define TAG_ENUMERATION_MUTATION        "objc_enumerationMutation"
+#define TAG_FAST_ENUMERATION_STATE      "__objcFastEnumerationState"
+
 static const char *TAG_GETCLASS;
 static const char *TAG_GETMETACLASS;
 static const char *TAG_MSGSEND;
@@ -1952,6 +1958,17 @@ synth_module_prologue (void)
   self_id = get_identifier ("self");
   ucmd_id = get_identifier ("_cmd");
 
+  /* Declare struct _objc_fast_enumeration_state { ... };  */
+  build_fast_enumeration_state_template ();
+  
+  /* void objc_enumeration_mutation (id) */
+  type = build_function_type (void_type_node,
+			      tree_cons (NULL_TREE, objc_object_type, NULL_TREE));
+  objc_enumeration_mutation_decl 
+    = add_builtin_function (TAG_ENUMERATION_MUTATION, type, 0, NOT_BUILT_IN, 
+			    NULL, NULL_TREE);
+  TREE_NOTHROW (objc_enumeration_mutation_decl) = 0;
+
 #ifdef OBJCPLUS
   pop_lang_context ();
 #endif
@@ -3596,13 +3613,25 @@ get_class_ivars (tree interface, bool inherited)
   return ivar_chain;
 }
 
+/* Create a temporary variable of type 'type'.  If 'name' is set, uses
+   the specified name, else use no name.  Returns the declaration of
+   the type.  The 'name' is mostly useful for debugging.
+*/
 static tree
-objc_create_temporary_var (tree type)
+objc_create_temporary_var (tree type, const char *name)
 {
   tree decl;
 
-  decl = build_decl (input_location,
-		     VAR_DECL, NULL_TREE, type);
+  if (name != NULL)
+    {
+      decl = build_decl (input_location,
+			 VAR_DECL, get_identifier (name), type);
+    }
+  else
+    {
+      decl = build_decl (input_location,
+			 VAR_DECL, NULL_TREE, type);
+    }
   TREE_USED (decl) = 1;
   DECL_ARTIFICIAL (decl) = 1;
   DECL_IGNORED_P (decl) = 1;
@@ -3687,7 +3716,7 @@ objc_build_exc_ptr (void)
       tree var = cur_try_context->caught_decl;
       if (!var)
 	{
-	  var = objc_create_temporary_var (objc_object_type);
+	  var = objc_create_temporary_var (objc_object_type, NULL);
 	  cur_try_context->caught_decl = var;
 	}
       return var;
@@ -3888,10 +3917,10 @@ next_sjlj_build_try_catch_finally (void)
 
   /* Create the declarations involved.  */
   t = xref_tag (RECORD_TYPE, get_identifier (UTAG_EXCDATA));
-  stack_decl = objc_create_temporary_var (t);
+  stack_decl = objc_create_temporary_var (t, NULL);
   cur_try_context->stack_decl = stack_decl;
 
-  rethrow_decl = objc_create_temporary_var (objc_object_type);
+  rethrow_decl = objc_create_temporary_var (objc_object_type, NULL);
   cur_try_context->rethrow_decl = rethrow_decl;
   TREE_CHAIN (rethrow_decl) = stack_decl;
 
@@ -9980,4 +10009,548 @@ objc_gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p)
 #endif
 }
 
+/* This routine returns true if TYP is a valid objc object type, 
+   suitable for messaging; false otherwise.
+*/
+
+static bool
+objc_type_valid_for_messaging (tree typ)
+{
+  if (!POINTER_TYPE_P (typ))
+    return false;
+
+  do
+    typ = TREE_TYPE (typ);  /* Remove indirections.  */
+  while (POINTER_TYPE_P (typ));
+
+  if (TREE_CODE (typ) != RECORD_TYPE)
+    return false;
+
+  return objc_is_object_id (typ) || TYPE_HAS_OBJC_INFO (typ);
+}
+
+/* Begin code generation for fast enumeration (foreach) ... */
+
+/* Defines
+
+  struct __objcFastEnumerationState
+   {
+     unsigned long state;
+     id            *itemsPtr;
+     unsigned long *mutationsPtr;
+     unsigned long extra[5];
+   };
+
+   Confusingly enough, NSFastEnumeration is then defined by libraries
+   to be the same structure.  
+*/
+
+static void
+build_fast_enumeration_state_template (void)
+{
+  tree decls, *chain = NULL;
+
+  /* { */
+  objc_fast_enumeration_state_template = objc_start_struct (get_identifier 
+							    (TAG_FAST_ENUMERATION_STATE));
+
+  /* unsigned long state; */
+  decls = add_field_decl (long_unsigned_type_node, "state", &chain);
+
+  /* id            *itemsPtr; */
+  add_field_decl (build_pointer_type (objc_object_type), 
+		  "itemsPtr", &chain);
+
+  /* unsigned long *mutationsPtr; */
+  add_field_decl (build_pointer_type (long_unsigned_type_node), 
+		  "mutationsPtr", &chain);
+
+  /* unsigned long extra[5]; */
+  add_field_decl (build_sized_array_type (long_unsigned_type_node, 5), 
+		  "extra", &chain);
+
+  /* } */
+  objc_finish_struct (objc_fast_enumeration_state_template, decls);
+}
+
+/*
+  'objc_finish_foreach_loop()' generates the code for an Objective-C
+  foreach loop.  The 'location' argument is the location of the 'for'
+  that starts the loop.  The 'object_expression' is the expression of
+  the 'object' that iterates; the 'collection_expression' is the
+  expression of the collection that we iterate over (we need to make
+  sure we evaluate this only once); the 'for_body' is the set of
+  statements to be executed in each iteration; 'break_label' and
+  'continue_label' are the break and continue labels which we need to
+  emit since the <statements> may be jumping to 'break_label' (if they
+  contain 'break') or to 'continue_label' (if they contain
+  'continue').
+
+  The syntax is
+  
+  for (<object expression> in <collection expression>)
+    <statements>
+
+  which is compiled into the following blurb:
+
+  {
+    id __objc_foreach_collection;
+    __objc_fast_enumeration_state __objc_foreach_enum_state;
+    unsigned long __objc_foreach_batchsize;
+    id __objc_foreach_items[16];
+    __objc_foreach_collection = <collection expression>;
+    __objc_foreach_enum_state = { 0 };
+    __objc_foreach_batchsize = [__objc_foreach_collection countByEnumeratingWithState: &__objc_foreach_enum_state  objects: __objc_foreach_items  count: 16];
+    
+    if (__objc_foreach_batchsize == 0)
+      <object expression> = nil;
+    else
+      {
+	unsigned long __objc_foreach_mutations_pointer = *__objc_foreach_enum_state.mutationsPtr;
+        next_batch:
+	  {
+	    unsigned long __objc_foreach_index;
+            __objc_foreach_index = 0;
+
+            next_object:
+	    if (__objc_foreach_mutation_pointer != *__objc_foreach_enum_state.mutationsPtr) objc_enumeration_mutation (<collection expression>);
+	    <object expression> = enumState.itemsPtr[__objc_foreach_index];
+	    <statements> [PS: inside <statments>, 'break' jumps to break_label and 'continue' jumps to continue_label]
+
+            continue_label:
+            __objc_foreach_index++;
+            if (__objc_foreach_index < __objc_foreach_batchsize) goto next_object;
+	    __objc_foreach_batchsize = [__objc_foreach_collection countByEnumeratingWithState: &__objc_foreach_enum_state  objects: __objc_foreach_items  count: 16];
+         }
+       if (__objc_foreach_batchsize != 0) goto next_batch;
+       <object expression> = nil;
+       break_label:
+      }
+  }
+
+  'statements' may contain a 'continue' or 'break' instruction, which
+  the user expects to 'continue' or 'break' the entire foreach loop.
+  We are provided the labels that 'break' and 'continue' jump to, so
+  we place them where we want them to jump to when they pick them.
+  
+  Optimization TODO: we could cache the IMP of
+  countByEnumeratingWithState:objects:count:.
+*/
+
+/* If you need to debug objc_finish_foreach_loop(), uncomment the following line.  */
+/* #define DEBUG_OBJC_FINISH_FOREACH_LOOP 1 */
+
+#ifdef DEBUG_OBJC_FINISH_FOREACH_LOOP
+#include "tree-pretty-print.h"
+#endif
+
+void
+objc_finish_foreach_loop (location_t location, tree object_expression, tree collection_expression, tree for_body, 
+			  tree break_label, tree continue_label)
+{
+  /* A tree representing the __objcFastEnumerationState struct type,
+     or NSFastEnumerationState struct, whatever we are using.  */
+  tree objc_fast_enumeration_state_type;
+
+  /* The trees representing the declarations of each of the local variables.  */
+  tree objc_foreach_collection_decl;
+  tree objc_foreach_enum_state_decl;
+  tree objc_foreach_items_decl;
+  tree objc_foreach_batchsize_decl;
+  tree objc_foreach_mutations_pointer_decl;
+  tree objc_foreach_index_decl;
+
+  /* A tree representing the selector countByEnumeratingWithState:objects:count:.  */
+  tree selector_name;
+
+  /* A tree representing the local bind.  */
+  tree bind;
+
+  /* A tree representing the external 'if (__objc_foreach_batchsize)' */
+  tree first_if;
+
+  /* A tree representing the 'else' part of 'first_if'  */
+  tree first_else;
+
+  /* A tree representing the 'next_batch' label.  */
+  tree next_batch_label_decl;
+
+  /* A tree representing the binding after the 'next_batch' label.  */
+  tree next_batch_bind;
+
+  /* A tree representing the 'next_object' label.  */
+  tree next_object_label_decl;
+
+  /* Temporary variables.  */
+  tree t;
+  int i;
+
+  if (object_expression == error_mark_node)
+    return;
+
+  if (collection_expression == error_mark_node)
+    return;
+
+  if (!objc_type_valid_for_messaging (TREE_TYPE (object_expression)))
+    {
+      error ("iterating variable in fast enumeration is not an object");
+      return;
+    }
+
+  if (!objc_type_valid_for_messaging (TREE_TYPE (collection_expression)))
+    {
+      error ("collection in fast enumeration is not an object");
+      return;
+    }
+
+  /* TODO: Check that object_expression is either a variable
+     declaration, or an lvalue.  */
+
+  /* This kludge is an idea from apple.  We use the
+     __objcFastEnumerationState struct implicitly defined by the
+     compiler, unless a NSFastEnumerationState struct has been defined
+     (by a Foundation library such as GNUstep Base) in which case, we
+     use that one.
+  */
+  objc_fast_enumeration_state_type = objc_fast_enumeration_state_template;
+  {
+    tree objc_NSFastEnumeration_type = lookup_name (get_identifier ("NSFastEnumerationState"));
+
+    if (objc_NSFastEnumeration_type)
+      {
+	/* TODO: We really need to check that
+	   objc_NSFastEnumeration_type is the same as ours!  */
+	if (TREE_CODE (objc_NSFastEnumeration_type) == TYPE_DECL)
+	  {
+	    /* If it's a typedef, use the original type.  */
+	    if (DECL_ORIGINAL_TYPE (objc_NSFastEnumeration_type))
+	      objc_fast_enumeration_state_type = DECL_ORIGINAL_TYPE (objc_NSFastEnumeration_type);
+	    else
+	      objc_fast_enumeration_state_type = TREE_TYPE (objc_NSFastEnumeration_type);	      
+	  }
+      }
+  }
+
+  /* { */
+  /* Done by c-parser.c.  */
+
+  /* type object; */
+  /* Done by c-parser.c.  */
+
+  /*  id __objc_foreach_collection */
+  objc_foreach_collection_decl = objc_create_temporary_var (objc_object_type, "__objc_foreach_collection");
+
+  /*  __objcFastEnumerationState __objc_foreach_enum_state; */
+  objc_foreach_enum_state_decl = objc_create_temporary_var (objc_fast_enumeration_state_type, "__objc_foreach_enum_state");
+  TREE_CHAIN (objc_foreach_enum_state_decl) = objc_foreach_collection_decl;
+
+  /* id __objc_foreach_items[16]; */
+  objc_foreach_items_decl = objc_create_temporary_var (build_sized_array_type (objc_object_type, 16), "__objc_foreach_items");
+  TREE_CHAIN (objc_foreach_items_decl) = objc_foreach_enum_state_decl;
+
+  /* unsigned long __objc_foreach_batchsize; */
+  objc_foreach_batchsize_decl = objc_create_temporary_var (long_unsigned_type_node, "__objc_foreach_batchsize");
+  TREE_CHAIN (objc_foreach_batchsize_decl) = objc_foreach_items_decl;
+
+  /* Generate the local variable binding.  */
+  bind = build3 (BIND_EXPR, void_type_node, objc_foreach_batchsize_decl, NULL, NULL);
+  SET_EXPR_LOCATION (bind, location);
+  TREE_SIDE_EFFECTS (bind) = 1;
+  
+  /*  __objc_foreach_collection = <collection expression>; */
+  t = build2 (MODIFY_EXPR, void_type_node, objc_foreach_collection_decl, collection_expression);
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (bind));
+
+  /*  __objc_foreach_enum_state.state = 0; */
+  t = build2 (MODIFY_EXPR, void_type_node, objc_build_component_ref (objc_foreach_enum_state_decl, 
+								     get_identifier ("state")),
+	      build_int_cst (long_unsigned_type_node, 0));
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (bind));
+
+  /*  __objc_foreach_enum_state.itemsPtr = NULL; */
+  t = build2 (MODIFY_EXPR, void_type_node, objc_build_component_ref (objc_foreach_enum_state_decl, 
+								     get_identifier ("itemsPtr")),
+	      null_pointer_node);
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (bind));
+
+  /*  __objc_foreach_enum_state.mutationsPtr = NULL; */
+  t = build2 (MODIFY_EXPR, void_type_node, objc_build_component_ref (objc_foreach_enum_state_decl, 
+								     get_identifier ("mutationsPtr")),
+	      null_pointer_node);
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (bind));
+
+  /*  __objc_foreach_enum_state.extra[0] = 0; */
+  /*  __objc_foreach_enum_state.extra[1] = 0; */
+  /*  __objc_foreach_enum_state.extra[2] = 0; */
+  /*  __objc_foreach_enum_state.extra[3] = 0; */
+  /*  __objc_foreach_enum_state.extra[4] = 0; */
+  for (i = 0; i < 5 ; i++)
+    {
+      t = build2 (MODIFY_EXPR, void_type_node,
+		  build_array_ref (location, objc_build_component_ref (objc_foreach_enum_state_decl, 
+								       get_identifier ("extra")),
+				   build_int_cst (NULL_TREE, i)),
+		  build_int_cst (long_unsigned_type_node, 0));
+      SET_EXPR_LOCATION (t, location);
+      append_to_statement_list (t, &BIND_EXPR_BODY (bind));
+    }
+    
+  /* __objc_foreach_batchsize = [__objc_foreach_collection countByEnumeratingWithState: &__objc_foreach_enum_state  objects: __objc_foreach_items  count: 16]; */
+  selector_name = get_identifier ("countByEnumeratingWithState:objects:count:");
+#ifdef OBJCPLUS
+  t = objc_finish_message_expr (objc_foreach_collection_decl, selector_name,
+				/* Parameters.  */
+				tree_cons    /* &__objc_foreach_enum_state */
+				(NULL_TREE, build_fold_addr_expr_loc (location, objc_foreach_enum_state_decl),
+				 tree_cons   /* __objc_foreach_items  */
+				 (NULL_TREE, objc_foreach_items_decl,
+				  tree_cons  /* 16 */
+				  (NULL_TREE, build_int_cst (NULL_TREE, 16), NULL_TREE))));
+#else
+  /* In C, we need to decay the __objc_foreach_items array that we are passing.  */
+  {
+    struct c_expr array;
+    array.value = objc_foreach_items_decl;
+    t = objc_finish_message_expr (objc_foreach_collection_decl, selector_name,
+				  /* Parameters.  */
+				  tree_cons    /* &__objc_foreach_enum_state */
+				  (NULL_TREE, build_fold_addr_expr_loc (location, objc_foreach_enum_state_decl),
+				   tree_cons   /* __objc_foreach_items  */
+				   (NULL_TREE, default_function_array_conversion (location, array).value,
+				    tree_cons  /* 16 */
+				    (NULL_TREE, build_int_cst (NULL_TREE, 16), NULL_TREE))));
+  }
+#endif
+  t = build2 (MODIFY_EXPR, void_type_node, objc_foreach_batchsize_decl, t);
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (bind));
+
+  /* if (__objc_foreach_batchsize == 0) */
+  first_if = build3 (COND_EXPR, void_type_node, 
+		     /* Condition.  */
+		     c_fully_fold 
+		     (c_common_truthvalue_conversion 
+		      (location, 
+		       build_binary_op (location,
+					EQ_EXPR, 
+					objc_foreach_batchsize_decl,
+					build_int_cst (long_unsigned_type_node, 0), 1)),
+		      false, NULL),
+		     /* Then block (we fill it in later).  */
+		     NULL_TREE,
+		     /* Else block (we fill it in later).  */
+		     NULL_TREE);
+  SET_EXPR_LOCATION (first_if, location);
+  append_to_statement_list (first_if, &BIND_EXPR_BODY (bind));
+
+  /* then <object expression> = nil; */
+  t = build2 (MODIFY_EXPR, void_type_node, object_expression, convert (objc_object_type, null_pointer_node));
+  SET_EXPR_LOCATION (t, location);
+  COND_EXPR_THEN (first_if) = t;
+
+  /* Now we build the 'else' part of the if; once we finish building
+     it, we attach it to first_if as the 'else' part.  */
+
+  /* else */
+  /* { */
+
+  /* unsigned long __objc_foreach_mutations_pointer; */
+  objc_foreach_mutations_pointer_decl = objc_create_temporary_var (long_unsigned_type_node, "__objc_foreach_mutations_pointer");
+
+  /* Generate the local variable binding.  */
+  first_else = build3 (BIND_EXPR, void_type_node, objc_foreach_mutations_pointer_decl, NULL, NULL);
+  SET_EXPR_LOCATION (first_else, location);
+  TREE_SIDE_EFFECTS (first_else) = 1;
+
+  /* __objc_foreach_mutations_pointer = *__objc_foreach_enum_state.mutationsPtr; */
+  t = build2 (MODIFY_EXPR, void_type_node, objc_foreach_mutations_pointer_decl, 
+	      build_indirect_ref (location, objc_build_component_ref (objc_foreach_enum_state_decl, 
+								      get_identifier ("mutationsPtr")),
+				  RO_UNARY_STAR));
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (first_else));
+
+  /* next_batch: */
+  next_batch_label_decl = create_artificial_label (location);
+  t = build1 (LABEL_EXPR, void_type_node, next_batch_label_decl); 
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (first_else));
+  
+  /* { */
+
+  /* unsigned long __objc_foreach_index; */
+  objc_foreach_index_decl = objc_create_temporary_var (long_unsigned_type_node, "__objc_foreach_index");
+
+  /* Generate the local variable binding.  */
+  next_batch_bind = build3 (BIND_EXPR, void_type_node, objc_foreach_index_decl, NULL, NULL);
+  SET_EXPR_LOCATION (next_batch_bind, location);
+  TREE_SIDE_EFFECTS (next_batch_bind) = 1;
+  append_to_statement_list (next_batch_bind, &BIND_EXPR_BODY (first_else));
+
+  /* __objc_foreach_index = 0; */
+  t = build2 (MODIFY_EXPR, void_type_node, objc_foreach_index_decl,
+	      build_int_cst (long_unsigned_type_node, 0));
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (next_batch_bind));
+
+  /* next_object: */
+  next_object_label_decl = create_artificial_label (location);
+  t = build1 (LABEL_EXPR, void_type_node, next_object_label_decl);
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (next_batch_bind));
+
+  /* if (__objc_foreach_mutation_pointer != *__objc_foreach_enum_state.mutationsPtr) objc_enumeration_mutation (<collection expression>); */
+  t = build3 (COND_EXPR, void_type_node, 
+	      /* Condition.  */
+	      c_fully_fold 
+	      (c_common_truthvalue_conversion 
+	       (location, 
+		build_binary_op 
+		(location,
+		 NE_EXPR, 
+		 objc_foreach_mutations_pointer_decl,
+		 build_indirect_ref (location, 
+				     objc_build_component_ref (objc_foreach_enum_state_decl, 
+							       get_identifier ("mutationsPtr")),
+				     RO_UNARY_STAR), 1)),
+	       false, NULL),
+	      /* Then block.  */
+	      build_function_call (input_location,
+				   objc_enumeration_mutation_decl,
+				   tree_cons (NULL, collection_expression, NULL)),
+	      /* Else block.  */
+	      NULL_TREE);
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (next_batch_bind));
+
+  /* <object expression> = enumState.itemsPtr[__objc_foreach_index]; */
+  t = build2 (MODIFY_EXPR, void_type_node, object_expression, 
+	      build_array_ref (location, objc_build_component_ref (objc_foreach_enum_state_decl, 
+								   get_identifier ("itemsPtr")),
+			       objc_foreach_index_decl));
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (next_batch_bind));
+
+  /* <statements> [PS: in <statments>, 'break' jumps to break_label and 'continue' jumps to continue_label] */
+  append_to_statement_list (for_body, &BIND_EXPR_BODY (next_batch_bind));
+
+  /* continue_label: */
+  if (continue_label)
+    {
+      t = build1 (LABEL_EXPR, void_type_node, continue_label);
+      SET_EXPR_LOCATION (t, location);
+      append_to_statement_list (t, &BIND_EXPR_BODY (next_batch_bind));
+    }
+
+  /* __objc_foreach_index++; */
+  t = build2 (MODIFY_EXPR, void_type_node, objc_foreach_index_decl, 
+	      build_binary_op (location,
+			       PLUS_EXPR,
+			       objc_foreach_index_decl,
+			       build_int_cst (long_unsigned_type_node, 1), 1));
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (next_batch_bind));
+
+  /* if (__objc_foreach_index < __objc_foreach_batchsize) goto next_object; */
+  t = build3 (COND_EXPR, void_type_node, 
+	      /* Condition.  */
+	      c_fully_fold 
+	      (c_common_truthvalue_conversion 
+	       (location, 
+		build_binary_op (location,
+				 LT_EXPR, 
+				 objc_foreach_index_decl,
+				 objc_foreach_batchsize_decl, 1)),
+	       false, NULL),
+	      /* Then block.  */
+	      build1 (GOTO_EXPR, void_type_node, next_object_label_decl),
+	      /* Else block.  */
+	      NULL_TREE);
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (next_batch_bind));
+  
+  /* __objc_foreach_batchsize = [__objc_foreach_collection countByEnumeratingWithState: &__objc_foreach_enum_state  objects: __objc_foreach_items  count: 16]; */
+#ifdef OBJCPLUS
+  t = objc_finish_message_expr (objc_foreach_collection_decl, selector_name,
+				/* Parameters.  */
+				tree_cons    /* &__objc_foreach_enum_state */
+				(NULL_TREE, build_fold_addr_expr_loc (location, objc_foreach_enum_state_decl),
+				 tree_cons   /* __objc_foreach_items  */
+				 (NULL_TREE, objc_foreach_items_decl,
+				  tree_cons  /* 16 */
+				  (NULL_TREE, build_int_cst (NULL_TREE, 16), NULL_TREE))));
+#else
+  /* In C, we need to decay the __objc_foreach_items array that we are passing.  */
+  {
+    struct c_expr array;
+    array.value = objc_foreach_items_decl;
+    t = objc_finish_message_expr (objc_foreach_collection_decl, selector_name,
+				  /* Parameters.  */
+				  tree_cons    /* &__objc_foreach_enum_state */
+				  (NULL_TREE, build_fold_addr_expr_loc (location, objc_foreach_enum_state_decl),
+				   tree_cons   /* __objc_foreach_items  */
+				   (NULL_TREE, default_function_array_conversion (location, array).value,
+				    tree_cons  /* 16 */
+				    (NULL_TREE, build_int_cst (NULL_TREE, 16), NULL_TREE))));
+  }
+#endif
+  t = build2 (MODIFY_EXPR, void_type_node, objc_foreach_batchsize_decl, t);
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (next_batch_bind));
+
+  /* } */
+
+  /* if (__objc_foreach_batchsize != 0) goto next_batch; */
+  t = build3 (COND_EXPR, void_type_node, 
+	      /* Condition.  */
+	      c_fully_fold 
+	      (c_common_truthvalue_conversion 
+	       (location, 
+		build_binary_op (location,
+				 NE_EXPR, 
+				 objc_foreach_batchsize_decl,
+				 build_int_cst (long_unsigned_type_node, 0), 1)),
+	       false, NULL),
+	      /* Then block.  */
+	      build1 (GOTO_EXPR, void_type_node, next_batch_label_decl),
+	      /* Else block.  */
+	      NULL_TREE);
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (first_else));
+
+  /* <object expression> = nil; */
+  t = build2 (MODIFY_EXPR, void_type_node, object_expression, convert (objc_object_type, null_pointer_node));
+  SET_EXPR_LOCATION (t, location);
+  append_to_statement_list (t, &BIND_EXPR_BODY (first_else));
+
+  /* break_label: */
+  if (break_label)
+    {
+      t = build1 (LABEL_EXPR, void_type_node, break_label);
+      SET_EXPR_LOCATION (t, location);
+      append_to_statement_list (t, &BIND_EXPR_BODY (first_else));
+    }
+
+  /* } */
+  COND_EXPR_ELSE (first_if) = first_else;
+
+  /* Do the whole thing.  */
+  add_stmt (bind);
+
+#ifdef DEBUG_OBJC_FINISH_FOREACH_LOOP
+  /* This will print to stderr the whole blurb generated by the
+     compiler while compiling (assuming the compiler doesn't crash
+     before getting here).
+   */
+  debug_generic_stmt (bind);
+#endif
+
+  /* } */
+  /* Done by c-parser.c  */
+}
+
 #include "gt-objc-objc-act.h"
diff --git a/gcc/objc/objc-act.h b/gcc/objc/objc-act.h
index 61312e950948e1c58daf79c72e25464a54c83d27..9f6ddcac7249e7b7b98e748b5bd4e39d2358e7a9 100644
--- a/gcc/objc/objc-act.h
+++ b/gcc/objc/objc-act.h
@@ -269,6 +269,9 @@ enum objc_tree_index
     OCTI_ASSIGN_GLOBAL_DECL,
     OCTI_ASSIGN_STRONGCAST_DECL,
 
+    OCTI_FAST_ENUM_STATE_TEMP,
+    OCTI_ENUM_MUTATION_DECL,
+
     OCTI_MAX
 };
 
@@ -433,5 +436,9 @@ extern GTY(()) tree objc_global_trees[OCTI_MAX];
 #define string_class_decl	objc_global_trees[OCTI_STRING_CLASS_DECL]
 #define internal_const_str_type	objc_global_trees[OCTI_INTERNAL_CNST_STR_TYPE]
 #define UOBJC_SUPER_decl	objc_global_trees[OCTI_SUPER_DECL]
+#define objc_fast_enumeration_state_template	\
+                                objc_global_trees[OCTI_FAST_ENUM_STATE_TEMP]
+#define objc_enumeration_mutation_decl		\
+                                objc_global_trees[OCTI_ENUM_MUTATION_DECL]
 
 #endif /* GCC_OBJC_ACT_H */
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 6e848cd166b029b309c4c5a57f9d1f4666ee0c04..e95e2b88874068f3251761d4f842bb3d0ff009a2 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,8 +1,45 @@
+2010-10-05  Nicola Pero  <nicola.pero@meta-innovation.com>
+
+	Implemented fast enumeration for Objective-C.
+	* objc.dg/foreach-1.m: New.
+	* objc.dg/foreach-2.m: New.
+	* objc.dg/foreach-3.m: New.
+	* objc.dg/foreach-4.m: New.
+	* objc.dg/foreach-5.m: New.
+	* objc.dg/foreach-6.m: New.
+	* objc.dg/foreach-7.m: New.
+
+	Merge from 'apple/trunk' branch on FSF servers:
+	2006-04-13 Fariborz Jahanian <fjahanian@apple.com>
+
+	Radar 4502236
+	* objc.dg/objc-foreach-5.m: New.	
+
+	2006-04-12 Fariborz Jahanian <fjahanian@apple.com>
+
+	Radar 4507230
+	* objc.dg/objc-foreach-4.m: New.
+
+	2006-03-13  Fariborz Jahanian <fjahanian@apple.com>
+
+	Radar 4472881
+	* objc.dg/objc-foreach-3.m: New.
+
+	2005-03-07 Fariborz Jahanian <fjahanian@apple.com>
+
+        Radar 4468498
+	* objc.dg/objc-foreach-2.m: New.
+
+	2006-02-15   Fariborz Jahanian <fjahanian@apple.com>
+
+	Radar 4294910
+	* objc.dg/objc-foreach-1.m: New
+
 2010-10-06  Hariharan Sandanagobalane <hariharan@picochip.com>
 
 	* gcc.c-torture/execute/cmpsi-2.c : Unsigned comparisons should use
 	unsigned values.
-
+	
 2010-10-05  Nicola Pero  <nicola.pero@meta-innovation.com>
 
 	PR objc++/28050
diff --git a/gcc/testsuite/objc.dg/foreach-1.m b/gcc/testsuite/objc.dg/foreach-1.m
new file mode 100644
index 0000000000000000000000000000000000000000..541b5835c356938e4107adf2a01916d61c0752a7
--- /dev/null
+++ b/gcc/testsuite/objc.dg/foreach-1.m
@@ -0,0 +1,81 @@
+/* Test basic Objective-C foreach syntax.  This tests iterations that
+   do nothing.
+*/
+/* FIXME: Run this test with the NeXT runtime as well.  */
+/* { dg-skip-if "" { *-*-* } { "-fnext-runtime" } { "" } } */
+/* { dg-do run } */
+
+#include <objc/objc.h>
+#include <objc/Object.h>
+extern void abort (void);
+/*
+struct __objcFastEnumerationState
+{
+  unsigned long state;
+  id            *itemsPtr;
+  unsigned long *mutationsPtr;
+  unsigned long extra[5];
+};
+*/
+@interface Object (NSFastEnumeration)
+- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState *)state
+                                     objects:(id *)stackbuf 
+                                       count:(unsigned int)len;
+@end
+
+int main (void)
+{
+  int test_variable = 0;
+  int counter = 0;
+  id array = nil;
+  id object = nil;
+
+  /* Test that 'for (object in array)' is recognized and that nothing
+     happens if array is nil.  */
+  for (object in array)
+    test_variable = 8;
+
+  if (test_variable == 8)
+    abort ();
+
+  if (object != nil)
+    abort ();
+
+  /* Test that if nothing is done, object is set to nil.  */
+  object = [Object new];
+
+  for (object in array)
+    ;
+
+  if (object != nil)
+    abort ();
+
+  /* Test that you can reference 'object' inside the body.  */
+  for (object in array)
+    object = nil;
+
+  if (object != nil)
+    abort ();
+
+  /* Test that 'for (id element in array) is recognized (and works).  */
+  for (id element in array)
+    test_variable = 8;
+
+  if (test_variable == 8)
+    abort ();
+
+  /* Test that you can reference 'object' inside the body.  */
+  for (id element in array)
+    element = nil;
+
+  /* Test that C for loops still work.  */
+  test_variable = 0;
+
+  for (counter = 0; counter < 4; counter++)
+    test_variable++;
+
+  if (test_variable != 4)
+    abort ();
+
+  return 0;
+}
diff --git a/gcc/testsuite/objc.dg/foreach-2.m b/gcc/testsuite/objc.dg/foreach-2.m
new file mode 100644
index 0000000000000000000000000000000000000000..e158502181395a51eabf5f12d9ff97187aff79dc
--- /dev/null
+++ b/gcc/testsuite/objc.dg/foreach-2.m
@@ -0,0 +1,279 @@
+/* Test basic Objective-C foreach syntax.  This tests iterations, with
+   the basic syntax 'for (object in array) statements'
+*/
+/* FIXME: Run this test with the NeXT runtime as well.  */
+/* { dg-skip-if "" { *-*-* } { "-fnext-runtime" } { "" } } */
+/* { dg-do run } */
+
+#include <objc/objc.h>
+#include <objc/Object.h>
+#include <objc/NXConstStr.h>
+#include <stdlib.h>
+extern void abort (void);
+/*
+struct __objcFastEnumerationState
+{
+  unsigned long state;
+  id            *itemsPtr;
+  unsigned long *mutationsPtr;
+  unsigned long extra[5];
+};
+*/
+
+ /* A mini-array implementation that can be used to test fast
+    enumeration.  You create the array with some objects; you can
+    mutate the array, and you can fast-enumerate it.
+ */
+@interface MyArray : Object
+{
+  unsigned int length;
+  id *objects;
+  unsigned long mutated;
+}
+- (id) initWithLength: (unsigned int)l  objects: (id *)o;
+- (void) mutate;
+- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState *)state
+                                     objects:(id *)stackbuf 
+                                       count:(unsigned long)len;
+@end
+
+@implementation MyArray : Object
+- (id) initWithLength: (unsigned int)l
+	      objects: (id *)o
+{
+  length = l;
+  objects = o;
+  mutated = 0;
+}
+- (void) mutate
+{
+  mutated = 1;
+}
+- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState*)state 
+		  		     objects: (id*)stackbuf
+			 	       count: (unsigned long)len
+{
+  unsigned long i, batch_size;
+
+  /* We keep how many objects we served in the state->state counter.  So the next batch
+     will contain up to length - state->state objects.  */
+  batch_size = length - state->state;
+
+  /* Make obvious adjustments.  */
+  if (batch_size < 0)
+    batch_size = 0;
+
+  if (batch_size > len)
+    batch_size = len;
+
+  /* Copy the objects.  */
+  for (i = 0; i < batch_size; i++)
+    stackbuf[i] = objects[i];
+
+  state->state += batch_size;
+  state->itemsPtr = stackbuf;
+  state->mutationsPtr = &mutated;
+
+  return batch_size;
+}
+@end
+
+int main (void)
+{
+  MyArray *array;
+  Object *object;
+  int test_variable, counter, i;
+  id *objects;
+
+  array = [[MyArray alloc] initWithLength: 0
+			   objects: NULL];
+
+  /* Test that an empty array does nothing.  */
+  for (object in array)
+    abort ();
+
+  if (object != nil)
+    abort ();
+
+  /* Test iterating over 1 object.  */
+  objects = malloc (sizeof (id) * 1);
+  objects[0] = @"One Object";
+
+  array = [[MyArray alloc] initWithLength: 1
+			   objects: objects];
+  
+  for (object in array)
+    printf ("%p\n", object);
+  
+  /* Test iterating over 20 objects.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  
+  for (object in array)
+    printf ("%p\n", object);
+
+  /* Test iterating over 200 objects.  */
+  objects = malloc (sizeof (id) * 200);
+  for (i = 0; i < 200; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 200
+			   objects: objects];
+  
+  counter = 0;
+  for (object in array)
+    {
+      if (object != nil)
+	counter++;
+    }
+
+  if (counter != 200)
+    abort ();
+
+  printf ("Counter was %d (should be 200)\n", counter);
+
+  /* Test iterating again over the same array.  */
+  counter = 0;
+  for (object in array)
+    {
+      if (object != nil)
+	counter++;
+    }
+
+  if (counter != 200)
+    abort ();
+
+  printf ("Counter was %d (should be 200)\n", counter);
+
+  /* Test nested iterations.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (object in array)
+    {
+      id another_object;
+      for (another_object in array)
+	if (another_object != nil)
+	  counter++;
+    }
+
+  printf ("Counter was %d (should be 400)\n", counter);
+
+  if (counter != 400)
+    abort ();
+
+  /* Test 'continue'.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (object in array)
+    {
+      if (counter == 15)
+	continue;
+
+      counter++;
+    }
+
+  printf ("Counter was %d (should be 15)\n", counter);
+
+  if (counter != 15)
+    abort ();
+
+  /* Test 'break'.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (object in array)
+    {
+      counter++;
+
+      if (counter == 15)
+	break;
+    }
+
+  printf ("Counter was %d (should be 15)\n", counter);
+
+  if (counter != 15)
+    abort ();
+
+  /* Test 'break' and 'continue' in nested iterations.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (object in array)
+    {
+      int local_counter = 0;
+      id another_object;
+
+      /* Each internal loop should increase counter by 24.  */
+      for (another_object in array)
+	{
+	  local_counter++;
+	  
+	  if (local_counter == 10)
+	    {
+	      counter = counter + 20;
+	      break;
+	    }
+
+	  if (local_counter >= 5)
+	    continue;
+
+	  counter++;
+	}
+
+      /* Exit after 4 iterations.  */
+      if (counter == 96)
+	break;
+    }
+
+  printf ("Counter was %d (should be 96)\n", counter);
+
+  if (counter != 96)
+    abort ();
+
+  /* Test that if we 'break', the object is set to the last one, while
+     if we run out of objects, it is set to 'nil'.  */
+  for (object in array)
+    ;
+
+  if (object != nil)
+    abort ();
+
+  for (object in array)
+    break;
+
+  if (object == nil)
+    abort ();
+
+  /* Test that C for loops still work.  */
+  test_variable = 0;
+
+  for (counter = 0; counter < 4; counter++)
+    test_variable++;
+
+  if (test_variable != 4)
+    abort ();
+
+  return 0;
+}
diff --git a/gcc/testsuite/objc.dg/foreach-3.m b/gcc/testsuite/objc.dg/foreach-3.m
new file mode 100644
index 0000000000000000000000000000000000000000..893631fd423cf8a45d154ee0566116a334ea7310
--- /dev/null
+++ b/gcc/testsuite/objc.dg/foreach-3.m
@@ -0,0 +1,114 @@
+/* Test basic Objective-C foreach syntax.  This tests the mutation.
+*/
+/* FIXME: Run this test with the NeXT runtime as well.  */
+/* { dg-skip-if "" { *-*-* } { "-fnext-runtime" } { "" } } */
+/* FIXME: This test should be run, and it succeeds if the program
+   aborts at the right time (when the mutation happens).  It currently
+   works, but how do we tell the testsuite to test for it ?
+*/
+/* { dg-do compile } */
+
+#include <objc/objc.h>
+#include <objc/Object.h>
+#include <objc/NXConstStr.h>
+#include <stdlib.h>
+extern void abort (void);
+/*
+struct __objcFastEnumerationState
+{
+  unsigned long state;
+  id            *itemsPtr;
+  unsigned long *mutationsPtr;
+  unsigned long extra[5];
+};
+*/
+
+ /* A mini-array implementation that can be used to test fast
+    enumeration.  You create the array with some objects; you can
+    mutate the array, and you can fast-enumerate it.
+ */
+@interface MyArray : Object
+{
+  unsigned int length;
+  id *objects;
+  unsigned long mutated;
+}
+- (id) initWithLength: (unsigned int)l  objects: (id *)o;
+- (void) mutate;
+- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState *)state
+                                     objects:(id *)stackbuf 
+                                       count:(unsigned long)len;
+@end
+
+@implementation MyArray : Object
+- (id) initWithLength: (unsigned int)l
+	      objects: (id *)o
+{
+  length = l;
+  objects = o;
+  mutated = 0;
+}
+- (void) mutate
+{
+  mutated = 1;
+}
+- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState*)state 
+		  		     objects: (id*)stackbuf
+			 	       count: (unsigned long)len
+{
+  unsigned long i, batch_size;
+
+  /* Change the mutationsPtr if 'mutate' is called.  */
+  state->mutationsPtr = &mutated;
+
+  /* We keep how many objects we served in the state->state counter.  So the next batch
+     will contain up to length - state->state objects.  */
+  batch_size = length - state->state;
+
+  /* Make obvious adjustments.  */
+  if (batch_size < 0)
+    batch_size = 0;
+
+  if (batch_size > len)
+    batch_size = len;
+
+  /* Copy the objects.  */
+  for (i = 0; i < batch_size; i++)
+    stackbuf[i] = objects[i];
+
+  state->state += batch_size;
+  state->itemsPtr = stackbuf;
+
+  return batch_size;
+}
+@end
+
+int main (void)
+{
+  MyArray *array;
+  Object *object;
+  int counter, i;
+  id *objects;
+
+  /* Test iterating over 20 objects, mutating after 15.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  
+  counter = 0;
+  for (object in array)
+    {
+      counter++;
+      printf ("%d\n", counter);
+      if (counter == 14)
+	{
+	  printf ("Mutating (should abort at next iteration)\n");
+	  [array mutate];
+	}
+    }
+
+  return 0;
+}
diff --git a/gcc/testsuite/objc.dg/foreach-4.m b/gcc/testsuite/objc.dg/foreach-4.m
new file mode 100644
index 0000000000000000000000000000000000000000..c9cd977b0958207d2a782cf6bca109f870e8b37a
--- /dev/null
+++ b/gcc/testsuite/objc.dg/foreach-4.m
@@ -0,0 +1,259 @@
+/* Test basic Objective-C foreach syntax.  This tests iterations, with
+   the declaration syntax 'for (id object in array) statements'
+*/
+/* FIXME: Run this test with the NeXT runtime as well.  */
+/* { dg-skip-if "" { *-*-* } { "-fnext-runtime" } { "" } } */
+/* { dg-do run } */
+
+#include <objc/objc.h>
+#include <objc/Object.h>
+#include <objc/NXConstStr.h>
+#include <stdlib.h>
+extern void abort (void);
+/*
+struct __objcFastEnumerationState
+{
+  unsigned long state;
+  id            *itemsPtr;
+  unsigned long *mutationsPtr;
+  unsigned long extra[5];
+};
+*/
+
+ /* A mini-array implementation that can be used to test fast
+    enumeration.  You create the array with some objects; you can
+    mutate the array, and you can fast-enumerate it.
+ */
+@interface MyArray : Object
+{
+  unsigned int length;
+  id *objects;
+  unsigned long mutated;
+}
+- (id) initWithLength: (unsigned int)l  objects: (id *)o;
+- (void) mutate;
+- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState *)state
+                                     objects:(id *)stackbuf 
+                                       count:(unsigned long)len;
+@end
+
+@implementation MyArray : Object
+- (id) initWithLength: (unsigned int)l
+	      objects: (id *)o
+{
+  length = l;
+  objects = o;
+  mutated = 0;
+}
+- (void) mutate
+{
+  mutated = 1;
+}
+- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState*)state 
+		  		     objects: (id*)stackbuf
+			 	       count: (unsigned long)len
+{
+  unsigned long i, batch_size;
+
+  /* We keep how many objects we served in the state->state counter.  So the next batch
+     will contain up to length - state->state objects.  */
+  batch_size = length - state->state;
+
+  /* Make obvious adjustments.  */
+  if (batch_size < 0)
+    batch_size = 0;
+
+  if (batch_size > len)
+    batch_size = len;
+
+  /* Copy the objects.  */
+  for (i = 0; i < batch_size; i++)
+    stackbuf[i] = objects[i];
+
+  state->state += batch_size;
+  state->itemsPtr = stackbuf;
+  state->mutationsPtr = &mutated;
+
+  return batch_size;
+}
+@end
+
+int main (void)
+{
+  MyArray *array;
+  int test_variable, counter, i;
+  id *objects;
+
+  array = [[MyArray alloc] initWithLength: 0
+			   objects: NULL];
+
+  /* Test that an empty array does nothing.  */
+  for (id object in array)
+    abort ();
+
+  /* Test iterating over 1 object.  */
+  objects = malloc (sizeof (id) * 1);
+  objects[0] = @"One Object";
+
+  array = [[MyArray alloc] initWithLength: 1
+			   objects: objects];
+  
+  for (id object in array)
+    printf ("%p\n", object);
+  
+  /* Test iterating over 20 objects.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  
+  for (id object in array)
+    printf ("%p\n", object);
+
+  /* Test iterating over 200 objects.  */
+  objects = malloc (sizeof (id) * 200);
+  for (i = 0; i < 200; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 200
+			   objects: objects];
+  
+  counter = 0;
+  for (id object in array)
+    {
+      if (object != nil)
+	counter++;
+    }
+
+  if (counter != 200)
+    abort ();
+
+  printf ("Counter was %d (should be 200)\n", counter);
+
+  /* Test iterating again over the same array.  */
+  counter = 0;
+  for (id object in array)
+    {
+      if (object != nil)
+	counter++;
+    }
+
+  if (counter != 200)
+    abort ();
+
+  printf ("Counter was %d (should be 200)\n", counter);
+
+  /* Test nested iterations.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (id object in array)
+    {
+      for (id another_object in array)
+	if (another_object != nil)
+	  counter++;
+    }
+
+  printf ("Counter was %d (should be 400)\n", counter);
+
+  if (counter != 400)
+    abort ();
+
+  /* Test 'continue'.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (id object in array)
+    {
+      if (counter == 15)
+	continue;
+
+      counter++;
+    }
+
+  printf ("Counter was %d (should be 15)\n", counter);
+
+  if (counter != 15)
+    abort ();
+
+  /* Test 'break'.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (id object in array)
+    {
+      counter++;
+
+      if (counter == 15)
+	break;
+    }
+
+  printf ("Counter was %d (should be 15)\n", counter);
+
+  if (counter != 15)
+    abort ();
+
+  /* Test 'break' and 'continue' in nested iterations.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (id object in array)
+    {
+      int local_counter = 0;
+
+      /* Each internal loop should increase counter by 24.  */
+      for (id another_object in array)
+	{
+	  local_counter++;
+	  
+	  if (local_counter == 10)
+	    {
+	      counter = counter + 20;
+	      break;
+	    }
+
+	  if (local_counter >= 5)
+	    continue;
+
+	  counter++;
+	}
+
+      /* Exit after 4 iterations.  */
+      if (counter == 96)
+	break;
+    }
+
+  printf ("Counter was %d (should be 96)\n", counter);
+
+  if (counter != 96)
+    abort ();
+
+  /* Test that C for loops still work.  */
+  test_variable = 0;
+
+  for (counter = 0; counter < 4; counter++)
+    test_variable++;
+
+  if (test_variable != 4)
+    abort ();
+
+  return 0;
+}
diff --git a/gcc/testsuite/objc.dg/foreach-5.m b/gcc/testsuite/objc.dg/foreach-5.m
new file mode 100644
index 0000000000000000000000000000000000000000..b3579970ea0862ab6c85db2d32d0c882f261994e
--- /dev/null
+++ b/gcc/testsuite/objc.dg/foreach-5.m
@@ -0,0 +1,258 @@
+/* Test basic Objective-C foreach syntax.  This tests that if you
+   define your own NSFastEnumeration struct, the compiler picks it up.
+*/
+/* FIXME: Run this test with the NeXT runtime as well.  */
+/* { dg-skip-if "" { *-*-* } { "-fnext-runtime" } { "" } } */
+/* { dg-do run } */
+
+#include <objc/objc.h>
+#include <objc/Object.h>
+#include <objc/NXConstStr.h>
+#include <stdlib.h>
+extern void abort (void);
+
+typedef struct
+{
+  unsigned long state;
+  id            *itemsPtr;
+  unsigned long *mutationsPtr;
+  unsigned long extra[5];
+} NSFastEnumerationState;
+
+/* A mini-array implementation that can be used to test fast
+   enumeration.  You create the array with some objects; you can
+   mutate the array, and you can fast-enumerate it.
+*/
+@interface MyArray : Object
+{
+  unsigned int length;
+  id *objects;
+  unsigned long mutated;
+}
+- (id) initWithLength: (unsigned int)l  objects: (id *)o;
+- (void) mutate;
+- (unsigned long)countByEnumeratingWithState: (NSFastEnumerationState *)state
+                                     objects:(id *)stackbuf 
+                                       count:(unsigned long)len;
+@end
+
+@implementation MyArray : Object
+- (id) initWithLength: (unsigned int)l
+	      objects: (id *)o
+{
+  length = l;
+  objects = o;
+  mutated = 0;
+}
+- (void) mutate
+{
+  mutated = 1;
+}
+- (unsigned long)countByEnumeratingWithState: (NSFastEnumerationState*)state 
+		  		     objects: (id*)stackbuf
+			 	       count: (unsigned long)len
+{
+  unsigned long i, batch_size;
+
+  /* We keep how many objects we served in the state->state counter.  So the next batch
+     will contain up to length - state->state objects.  */
+  batch_size = length - state->state;
+
+  /* Make obvious adjustments.  */
+  if (batch_size < 0)
+    batch_size = 0;
+
+  if (batch_size > len)
+    batch_size = len;
+
+  /* Copy the objects.  */
+  for (i = 0; i < batch_size; i++)
+    stackbuf[i] = objects[i];
+
+  state->state += batch_size;
+  state->itemsPtr = stackbuf;
+  state->mutationsPtr = &mutated;
+
+  return batch_size;
+}
+@end
+
+int main (void)
+{
+  MyArray *array;
+  int test_variable, counter, i;
+  id *objects;
+
+  array = [[MyArray alloc] initWithLength: 0
+			   objects: NULL];
+
+  /* Test that an empty array does nothing.  */
+  for (id object in array)
+    abort ();
+
+  /* Test iterating over 1 object.  */
+  objects = malloc (sizeof (id) * 1);
+  objects[0] = @"One Object";
+
+  array = [[MyArray alloc] initWithLength: 1
+			   objects: objects];
+  
+  for (id object in array)
+    printf ("%p\n", object);
+  
+  /* Test iterating over 20 objects.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  
+  for (id object in array)
+    printf ("%p\n", object);
+
+  /* Test iterating over 200 objects.  */
+  objects = malloc (sizeof (id) * 200);
+  for (i = 0; i < 200; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 200
+			   objects: objects];
+  
+  counter = 0;
+  for (id object in array)
+    {
+      if (object != nil)
+	counter++;
+    }
+
+  if (counter != 200)
+    abort ();
+
+  printf ("Counter was %d (should be 200)\n", counter);
+
+  /* Test iterating again over the same array.  */
+  counter = 0;
+  for (id object in array)
+    {
+      if (object != nil)
+	counter++;
+    }
+
+  if (counter != 200)
+    abort ();
+
+  printf ("Counter was %d (should be 200)\n", counter);
+
+  /* Test nested iterations.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (id object in array)
+    {
+      for (id another_object in array)
+	if (another_object != nil)
+	  counter++;
+    }
+
+  printf ("Counter was %d (should be 400)\n", counter);
+
+  if (counter != 400)
+    abort ();
+
+  /* Test 'continue'.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (id object in array)
+    {
+      if (counter == 15)
+	continue;
+
+      counter++;
+    }
+
+  printf ("Counter was %d (should be 15)\n", counter);
+
+  if (counter != 15)
+    abort ();
+
+  /* Test 'break'.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (id object in array)
+    {
+      counter++;
+
+      if (counter == 15)
+	break;
+    }
+
+  printf ("Counter was %d (should be 15)\n", counter);
+
+  if (counter != 15)
+    abort ();
+
+  /* Test 'break' and 'continue' in nested iterations.  */
+  objects = malloc (sizeof (id) * 20);
+  for (i = 0; i < 20; i++)
+    objects[i] = @"object";
+  
+  array = [[MyArray alloc] initWithLength: 20
+			   objects: objects];
+  counter = 0;
+  for (id object in array)
+    {
+      int local_counter = 0;
+
+      /* Each internal loop should increase counter by 24.  */
+      for (id another_object in array)
+	{
+	  local_counter++;
+	  
+	  if (local_counter == 10)
+	    {
+	      counter = counter + 20;
+	      break;
+	    }
+
+	  if (local_counter >= 5)
+	    continue;
+
+	  counter++;
+	}
+
+      /* Exit after 4 iterations.  */
+      if (counter == 96)
+	break;
+    }
+
+  printf ("Counter was %d (should be 96)\n", counter);
+
+  if (counter != 96)
+    abort ();
+
+  /* Test that C for loops still work.  */
+  test_variable = 0;
+
+  for (counter = 0; counter < 4; counter++)
+    test_variable++;
+
+  if (test_variable != 4)
+    abort ();
+
+  return 0;
+}
diff --git a/gcc/testsuite/objc.dg/foreach-6.m b/gcc/testsuite/objc.dg/foreach-6.m
new file mode 100644
index 0000000000000000000000000000000000000000..7a6b9609d8a1d0ec7827c6015ace4625d8ea5335
--- /dev/null
+++ b/gcc/testsuite/objc.dg/foreach-6.m
@@ -0,0 +1,52 @@
+/* Test basic Objective-C foreach syntax.  This tests warnings and errors.  */
+/* FIXME: Run this test with the NeXT runtime as well.  */
+/* { dg-skip-if "" { *-*-* } { "-fnext-runtime" } { "" } } */
+/* { dg-do compile } */
+
+#include <objc/objc.h>
+#include <objc/Object.h>
+extern void abort (void);
+/*
+struct __objcFastEnumerationState
+{
+  unsigned long state;
+  id            *itemsPtr;
+  unsigned long *mutationsPtr;
+  unsigned long extra[5];
+};
+*/
+@interface Object (NSFastEnumeration)
+- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState *)state
+                                     objects:(id *)stackbuf 
+                                       count:(unsigned int)len;
+- (id) enumerator;
+@end
+
+int main (void)
+{
+  id array = nil;
+  id object = nil;
+
+  for (object in array) /* Ok */
+    ;
+
+  for (object in nil) /* Ok */
+    ;
+
+  for (object in) /* { dg-error "missing collection in fast enumeration" } */
+    ;
+
+  for (object = nil in array) /* { dg-error "invalid iterating variable in fast enumeration" } */
+    ;
+
+  for (object in [object enumerator]) /* Ok */
+    ;
+
+  for (12 in array) /* { dg-error "invalid iterating variable in fast enumeration" } */
+    ; /* { dg-error "iterating variable in fast enumeration is not an object" } */
+
+  for (object in 12)
+    ; /* { dg-error "collection in fast enumeration is not an object" } */
+
+  return 0;
+}
diff --git a/gcc/testsuite/objc.dg/foreach-7.m b/gcc/testsuite/objc.dg/foreach-7.m
new file mode 100644
index 0000000000000000000000000000000000000000..42bca82e3b953f6e0b9c4dd97ffbac48073a83d1
--- /dev/null
+++ b/gcc/testsuite/objc.dg/foreach-7.m
@@ -0,0 +1,60 @@
+/* Test basic Objective-C foreach syntax.  This tests warnings and errors.  */
+/* FIXME: Run this test with the NeXT runtime as well.  */
+/* { dg-skip-if "" { *-*-* } { "-fnext-runtime" } { "" } } */
+/* { dg-do compile } */
+
+#include <objc/objc.h>
+#include <objc/Object.h>
+extern void abort (void);
+/*
+struct __objcFastEnumerationState
+{
+  unsigned long state;
+  id            *itemsPtr;
+  unsigned long *mutationsPtr;
+  unsigned long extra[5];
+};
+*/
+@interface Object (NSFastEnumeration)
+- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState *)state
+                                     objects:(id *)stackbuf 
+                                       count:(unsigned int)len;
+- (id) enumerator;
+@end
+
+void function (void)
+{
+  return;
+}
+
+id object_function (void)
+{
+  return nil;
+}
+
+int main (void)
+{
+  id array = nil;
+  id object = nil;
+
+  for (typedef int my_typedef in array) /* { dg-error "declaration of non-variable" } */
+    ; /* { dg-error "iterating variable in fast enumeration is not an object" } */
+
+  for (function () in nil) /* { dg-error "invalid iterating variable in fast enumeration" } */
+    ; /* { dg-error "iterating variable in fast enumeration is not an object" } */
+
+  for (object_function () in nil) /* { dg-error "invalid iterating variable in fast enumeration" } */
+    ;
+
+  for ([object enumerator] in array) /* { dg-error "invalid iterating variable in fast enumeration" } */
+    ;
+
+  for (object = nil in array) /* { dg-error "invalid iterating variable in fast enumeration" } */
+    ;
+
+  for (id key, value in array) /* { dg-error "multiple iterating variables in fast enumeration" } */
+    ;
+
+  return 0;
+}
+
diff --git a/gcc/testsuite/objc.dg/objc-foreach-1.m b/gcc/testsuite/objc.dg/objc-foreach-1.m
new file mode 100644
index 0000000000000000000000000000000000000000..81f5dae0c2f292ee9171e73643ca32d58566be17
--- /dev/null
+++ b/gcc/testsuite/objc.dg/objc-foreach-1.m
@@ -0,0 +1,41 @@
+/* Syntax check for the new foreach statement. */
+/* { dg-do compile } */
+
+typedef struct objc_class *Class;
+
+typedef struct objc_object {
+ Class isa;
+} *id;
+
+
+@interface MyList 
+@end
+
+@implementation MyList
+- (unsigned int)countByEnumeratingWithState:(struct __objcFastEnumerationState *)state objects:(id *)items count:(unsigned int)stackcount
+{
+        return 0;
+}
+- (void)addObject:object {
+}
+
+@end
+
+@interface MyList (BasicTest)
+- (void)compilerTestAgainst;
+@end
+void BEGIN();
+void INFORLOOP();
+void END();
+@implementation MyList (BasicTest)
+- (void)compilerTestAgainst {
+
+	BEGIN();
+	for (id elem in (self)) 
+	  if (elem)
+	    INFORLOOP();
+
+	END();
+}
+@end
+
diff --git a/gcc/testsuite/objc.dg/objc-foreach-2.m b/gcc/testsuite/objc.dg/objc-foreach-2.m
new file mode 100644
index 0000000000000000000000000000000000000000..a01f004fec6cf7262867c533beb622200fa3b8c4
--- /dev/null
+++ b/gcc/testsuite/objc.dg/objc-foreach-2.m
@@ -0,0 +1,41 @@
+/* Syntax check for the new foreach statement. */
+/* { dg-do compile } */
+
+typedef struct objc_class *Class;
+
+typedef struct objc_object {
+ Class isa;
+} *id;
+
+
+@interface MyList 
+@end
+
+@implementation MyList
+- (unsigned int)countByEnumeratingWithState:(struct __objcFastEnumerationState *)state objects:(id *)items count:(unsigned int)stackcount
+{
+        return 0;
+}
+- (void)addObject:object {
+}
+
+@end
+
+@interface MyList (BasicTest)
+- (void)compilerTestAgainst;
+@end
+void BEGIN();
+void INFORLOOP();
+void END();
+@implementation MyList (BasicTest)
+- (void)compilerTestAgainst {
+
+	id elem;
+	BEGIN();
+	for (elem in (self)) 
+	  if (elem)
+	    INFORLOOP();
+	END();
+}
+@end
+
diff --git a/gcc/testsuite/objc.dg/objc-foreach-3.m b/gcc/testsuite/objc.dg/objc-foreach-3.m
new file mode 100644
index 0000000000000000000000000000000000000000..922db39e7481e8b6a20d7e23ae2e32ad8fb8a465
--- /dev/null
+++ b/gcc/testsuite/objc.dg/objc-foreach-3.m
@@ -0,0 +1,42 @@
+/* Syntax check for the new foreach statement. 
+   Use of declaration in loop-header without requiring c99 mode. */
+/* { dg-do compile } */
+
+typedef struct objc_class *Class;
+
+typedef struct objc_object {
+ Class isa;
+} *id;
+
+
+@interface MyList 
+@end
+
+@implementation MyList
+- (unsigned int)countByEnumeratingWithState:(struct __objcFastEnumerationState *)state objects:(id *)items count:(unsigned int)stackcount
+{
+        return 0;
+}
+- (void)addObject:object {
+}
+
+@end
+
+@interface MyList (BasicTest)
+- (void)compilerTestAgainst;
+@end
+void BEGIN();
+void INFORLOOP();
+void END();
+@implementation MyList (BasicTest)
+- (void)compilerTestAgainst {
+
+	BEGIN();
+	for (id elem in (self)) 
+	  if (elem)
+	    INFORLOOP();
+
+	END();
+}
+@end
+
diff --git a/gcc/testsuite/objc.dg/objc-foreach-4.m b/gcc/testsuite/objc.dg/objc-foreach-4.m
new file mode 100644
index 0000000000000000000000000000000000000000..76e429e69417012087e71819511497ee52a02f2d
--- /dev/null
+++ b/gcc/testsuite/objc.dg/objc-foreach-4.m
@@ -0,0 +1,17 @@
+/* Test for valid objc objects used in a for-each statement. */
+/* FIXME: Run this test with the GNU runtime as well.  */
+/* { dg-skip-if "" { *-*-* } { "-fgnu-runtime" } { "" } } */
+/* { dg-do compile { target *-*-darwin* } } */
+#include <Foundation/Foundation.h>
+
+// gcc -o foo foo.m -framework Foundation
+
+int main (int argc, char const* argv[]) {
+    NSAutoreleasePool * pool = [[NSAutoreleasePool alloc] init];
+    NSArray * arr = [NSArray arrayWithObjects:@"A", @"B", @"C", nil];
+    for (NSString * foo in arr) { 
+      NSLog(@"foo is %@", foo);
+    }
+    [pool release];
+    return 0;
+}
diff --git a/gcc/testsuite/objc.dg/objc-foreach-5.m b/gcc/testsuite/objc.dg/objc-foreach-5.m
new file mode 100644
index 0000000000000000000000000000000000000000..95a950375a492b16a3360b8de250af88e44352e9
--- /dev/null
+++ b/gcc/testsuite/objc.dg/objc-foreach-5.m
@@ -0,0 +1,37 @@
+/* FIXME: Run this test with the GNU runtime as well.  */
+/* { dg-skip-if "" { *-*-* } { "-fgnu-runtime" } { "" } } */
+/* { dg-do compile { target *-*-darwin* } } */
+#import <Foundation/Foundation.h>
+
+NSArray * createTestVictim(unsigned capacity) {
+    NSMutableArray * arr = [[NSMutableArray alloc] initWithCapacity:capacity];
+    int x = 0;
+
+    for(x = 0; x < capacity; x++) {
+        NSNumber * num = [NSNumber numberWithInteger:x];
+        [arr addObject:num];
+    }
+    
+    NSArray * immutableCopy = [arr copy];
+    [arr release];
+    
+    return immutableCopy;
+}
+
+void addStuffUp(NSArray * values) {
+    NSInteger accumulator = 0;
+//    for (id item in values) {
+    id item;
+    for (item in values) {
+        accumulator += [item integerValue];
+    }
+}
+
+int main (int argc, char const* argv[]) {
+    NSAutoreleasePool * pool = [[NSAutoreleasePool alloc] init];
+    NSArray * target = createTestVictim(10);
+    addStuffUp(target);
+    [pool release];
+    return 0;
+}
+/* { dg-final { scan-assembler "_addStuffUp:" } } */
diff --git a/libobjc/ChangeLog b/libobjc/ChangeLog
index b1590c443744fbfbf5ab355bd9ac212bec41927c..ac51fcb3c50517cfcf1b856781ab0205d94e1018 100644
--- a/libobjc/ChangeLog
+++ b/libobjc/ChangeLog
@@ -1,3 +1,11 @@
+2010-10-06  Nicola Pero  <nicola.pero@meta-innovation.com>
+
+	Implemented fast enumeration for Objective-C.
+	* Makefile.in (C_SOURCE_FILES): Added objc-foreach.c.
+	(OBJC_H): Added runtime.h
+	* objc-foreach.c: New file.
+	* objc/runtime.h: New file.
+	
 2010-09-30  Kai Tietz  <kai.tietz@onevision.com>
 
 	* objc/deprecated/struct_objc_class.h: Add padding
diff --git a/libobjc/Makefile.in b/libobjc/Makefile.in
index 71a3a2e21c27a22acb6bb35609a265ebfce0ed7e..d99ab26a0a67302db2d09bebfb9be8e2872c103f 100644
--- a/libobjc/Makefile.in
+++ b/libobjc/Makefile.in
@@ -120,6 +120,7 @@ OBJC_H = \
   message.h \
   objc-api.h \
   objc-decls.h \
+  runtime.h \
   thr.h \
   \
   hash.h \
@@ -163,6 +164,7 @@ C_SOURCE_FILES = \
    init.c \
    memory.c \
    nil_method.c \
+   objc-foreach.c \
    objc-sync.c \
    objects.c \
    sarray.c \
diff --git a/libobjc/objc-foreach.c b/libobjc/objc-foreach.c
new file mode 100644
index 0000000000000000000000000000000000000000..83a91011d12cb979065e72ccec986722cf911c75
--- /dev/null
+++ b/libobjc/objc-foreach.c
@@ -0,0 +1,52 @@
+/* GNU Objective C Runtime 'fast enumeration' implementation
+   Copyright (C) 2010 Free Software Foundation, Inc.
+   Contributed by Nicola Pero <nicola.pero@meta-innovation.com>
+
+This file is part of GCC.
+
+GCC is free software; you can redistribute it and/or modify it under the
+terms of the GNU General Public License as published by the Free Software
+Foundation; either version 3, or (at your option) any later version.
+
+GCC is distributed in the hope that it will be useful, but WITHOUT ANY
+WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
+FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
+details.
+
+Under Section 7 of GPL version 3, you are granted additional
+permissions described in the GCC Runtime Library Exception, version
+3.1, as published by the Free Software Foundation.
+
+You should have received a copy of the GNU General Public License and
+a copy of the GCC Runtime Library Exception along with this program;
+see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
+<http://www.gnu.org/licenses/>.  */
+
+/*
+  This file implements objc_enumeration_mutation() and
+  objc_set_enumeration_mutation_handler(), the two functions required
+  to handle mutations during a fast enumeration.
+*/
+#include "objc/runtime.h"           /* For objc_enumerationMutation() and objc_set_enumeration_mutation_handler() */
+#include "objc-private/error.h"     /* For _objc_abort() */
+
+/* The enumeration mutation handler currently in use.  */
+static void (*__objc_enumeration_mutation_handler)(id) = NULL;
+
+void
+objc_set_enumeration_mutation_handler (void (*handler)(id))
+{
+  __objc_enumeration_mutation_handler = handler;
+}
+
+void
+objc_enumerationMutation (id collection)
+{
+  if (__objc_enumeration_mutation_handler != NULL)
+    (*__objc_enumeration_mutation_handler) (collection);
+
+  /* We always abort if we get here; there is no point in going on as
+     the next iteration in the fast enumeration would probably go
+     deeply wrong.  */
+  _objc_abort ("Collection %p mutated during fast enumeration", collection);
+}  
diff --git a/libobjc/objc/runtime.h b/libobjc/objc/runtime.h
new file mode 100644
index 0000000000000000000000000000000000000000..7b16f1b09eac08c1ce9a19c37870ce394132addf
--- /dev/null
+++ b/libobjc/objc/runtime.h
@@ -0,0 +1,88 @@
+/* GNU Objective-C Runtime API.
+   Copyright (C) 2010 Free Software Foundation, Inc.
+   Contributed by Nicola Pero <nicola.pero@meta-innovation.com>
+
+This file is part of GCC.
+
+GCC is free software; you can redistribute it and/or modify it
+under the terms of the GNU General Public License as published by the
+Free Software Foundation; either version 3, or (at your option) any
+later version.
+
+GCC is distributed in the hope that it will be useful, but WITHOUT
+ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public
+License for more details.
+
+Under Section 7 of GPL version 3, you are granted additional
+permissions described in the GCC Runtime Library Exception, version
+3.1, as published by the Free Software Foundation.
+
+You should have received a copy of the GNU General Public License and
+a copy of the GCC Runtime Library Exception along with this program;
+see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
+<http://www.gnu.org/licenses/>.  */
+
+#ifndef __objc_runtime_INCLUDE_GNU
+#define __objc_runtime_INCLUDE_GNU
+
+#include "objc.h"
+
+/* The following is temporary, until all code from objc-api.h has been
+   moved into this file and objc-api.h will include runtime.h.  */
+#include "objc-api.h"
+
+/* 'objc_enumerationMutation()' is called when a collection is
+   mutated while being "fast enumerated".  That is a hard error, and
+   objc_enumerationMutation is called to deal with it.  'collection'
+   is the collection object that was mutated during an enumeration.
+
+   objc_enumerationMutation() will invoke the mutation handler if any
+   is set.  Then, it will abort the program.
+
+   Compatibility note: the Apple runtime will not abort the program
+   after calling the mutation handler.
+ */
+objc_EXPORT void objc_enumerationMutation (id collection);
+
+/* 'objc_set_enumeration_mutation_handler' can be used to set a
+   function that will be called (instead of aborting) when a fast
+   enumeration is mutated during enumeration.  The handler will be
+   called with the 'collection' being mutated as the only argument and
+   it should not return; it should either exit the program, or could
+   throw an exception.  The recommended implementation is to throw an
+   exception - the user can then use exception handlers to deal with
+   it.
+
+   This function is not thread safe (other threads may be trying to
+   invoke the enumeration mutation handler while you are changing it!)
+   and should be called during during the program initialization
+   before threads are started.  It is mostly reserved for "Foundation"
+   libraries; in the case of GNUstep, GNUstep Base may be using this
+   function to improve the standard enumeration mutation handling.
+   You probably shouldn't use this function unless you are writing
+   your own Foundation library.
+*/
+objc_EXPORT void objc_set_enumeration_mutation_handler (void (*handler)(id));
+
+/* This structure (used during fast enumeration) is automatically
+   defined by the compiler (it is as if this definition was always
+   included in all Objective-C files).  Note that it is usually
+   defined again with the name of NSFastEnumeration by "Foundation"
+   libraries such as GNUstep Base.  And if NSFastEnumeration is
+   defined, the compiler will use it instead of
+   __objcFastEnumerationState when doing fast enumeration.
+*/
+/*
+struct __objcFastEnumerationState
+{
+  unsigned long state;
+  id            *itemsPtr;
+  unsigned long *mutationsPtr;
+  unsigned long extra[5];
+};
+*/
+/* For compatibility with the Apple/NeXT runtime.  */
+#define objc_setEnumerationMutationHandler objc_set_enumeration_mutation_handler
+
+#endif