This is the mail archive of the gcc-patches@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

__builtin_offsetof revisited


Whether or not the semantics are 100% perfect for C++, the result is
the same as what we have currently.  We can argue over the precise
semantics as a separate patch.  In the meantime, this has been blocking
other changes needed for better optimization.

Tested on i686-linux.


r~


2004-06-01  Richard Henderson  <rth@redhat.com>
            Andrew Pinski  <pinskia@physics.uc.edu>

        * c-parse.in (OFFSETOF, offsetof_member_designator): New.
        (primary): Handle offsetof.  Add error productions for faux functions.
        Move component_ref objc checking to build_component_ref.
        (reswords): Add offsetof.
        (rid_to_yy): Add offsetof.
        * c-tree.h (build_offsetof): Declare.
        * c-common.h (objc_is_public): Declare.
        * c-typeck.c (build_component_ref): Check objc_is_public.
        (build_offsetof): New.
        * stub-objc.c (objc_is_public): New.
        * objc/objc-act.c, objc/objc-act.h (objc_is_public): Rename
        from is_public.
        * ginclude/stddef.h (offsetof): Use __builtin_offsetof.
        * doc/extend.texi (Offsetof): Move from C++ section to C section
        and rewrite for __builtin_offsetof.
cp/
        * lex.c (reswords): Rename "__offsetof" to "__builtin_offsetof".
        * parser.c (struct cp_parser): Remove in_offsetof.
        (cp_parser_new): Don't set it.
        (cp_parser_unary_expression): Don't check it.
        (cp_parser_postfix_open_square_expression): Split out from ...
        (cp_parser_postfix_expression): ... here.
        (cp_parser_postfix_dot_deref_expression): Likewise.
        (cp_parser_builtin_offsetof): New.
        (cp_parser_primary_expression): Use it.
testsuite/
        * g++.dg/template/dependent-expr4.C: Use __builtin_offsetof.

Index: gcc/c-common.h
===================================================================
RCS file: /cvs/gcc/gcc/gcc/c-common.h,v
retrieving revision 1.229
diff -u -p -r1.229 c-common.h
--- gcc/c-common.h	30 May 2004 23:53:26 -0000	1.229
+++ gcc/c-common.h	1 Jun 2004 15:03:45 -0000
@@ -1236,6 +1236,7 @@ extern tree objc_message_selector (void)
 extern tree lookup_objc_ivar (tree);
 extern void *get_current_scope (void);
 extern void objc_mark_locals_volatile (void *);
+extern int objc_is_public (tree, tree);
 
 /* In c-ppoutput.c  */
 extern void init_pp_output (FILE *);
Index: gcc/c-parse.in
===================================================================
RCS file: /cvs/gcc/gcc/gcc/c-parse.in,v
retrieving revision 1.205
diff -u -p -r1.205 c-parse.in
--- gcc/c-parse.in	15 May 2004 23:07:45 -0000	1.205
+++ gcc/c-parse.in	1 Jun 2004 15:03:46 -0000
@@ -146,7 +146,7 @@ do {									\
 %token ATTRIBUTE EXTENSION LABEL
 %token REALPART IMAGPART VA_ARG CHOOSE_EXPR TYPES_COMPATIBLE_P
 %token PTR_VALUE PTR_BASE PTR_EXTENT
-%token FUNC_NAME
+%token FUNC_NAME OFFSETOF
 
 /* Add precedence rules to solve dangling else s/r conflict */
 %nonassoc IF
@@ -199,6 +199,7 @@ do {									\
 %type <ttype> maybe_type_quals_attrs typespec_nonattr typespec_attr
 %type <ttype> typespec_reserved_nonattr typespec_reserved_attr
 %type <ttype> typespec_nonreserved_nonattr
+%type <ttype> offsetof_member_designator
 
 %type <ttype> scspec SCSPEC STATIC TYPESPEC TYPE_QUAL maybe_volatile
 %type <ttype> initdecls notype_initdecls initdcl notype_initdcl init
@@ -674,17 +675,25 @@ primary:
 	| VA_ARG '(' expr_no_commas ',' typename ')'
 		{ $$ = build_va_arg ($3, groktypename ($5)); }
 
-      | CHOOSE_EXPR '(' expr_no_commas ',' expr_no_commas ',' expr_no_commas ')'
+	| OFFSETOF '(' typename ',' offsetof_member_designator ')'
+		{ $$ = build_offsetof (groktypename ($3), $5); }
+	| OFFSETOF '(' error ')'
+		{ $$ = error_mark_node; }
+	| CHOOSE_EXPR '(' expr_no_commas ',' expr_no_commas ','
+			  expr_no_commas ')'
 		{
                   tree c;
 
                   c = fold ($3);
                   STRIP_NOPS (c);
                   if (TREE_CODE (c) != INTEGER_CST)
-                    error ("first argument to __builtin_choose_expr not a constant");
+                    error ("first argument to __builtin_choose_expr not"
+			   " a constant");
                   $$ = integer_zerop (c) ? $7 : $5;
 		}
-      | TYPES_COMPATIBLE_P '(' typename ',' typename ')'
+	| CHOOSE_EXPR '(' error ')'
+		{ $$ = error_mark_node; }
+	| TYPES_COMPATIBLE_P '(' typename ',' typename ')'
 		{
 		  tree e1, e2;
 
@@ -694,27 +703,16 @@ primary:
 		  $$ = comptypes (e1, e2, COMPARE_STRICT)
 		    ? build_int_2 (1, 0) : build_int_2 (0, 0);
 		}
+	| TYPES_COMPATIBLE_P '(' error ')'
+		{ $$ = error_mark_node; }
 	| primary '[' expr ']'   %prec '.'
 		{ $$ = build_array_ref ($1, $3); }
 	| primary '.' identifier
-		{
-@@ifobjc
-		    if (!is_public ($1, $3))
-		      $$ = error_mark_node;
-		    else
-@@end_ifobjc
-		      $$ = build_component_ref ($1, $3);
-		}
+		{ $$ = build_component_ref ($1, $3); }
 	| primary POINTSAT identifier
 		{
                   tree expr = build_indirect_ref ($1, "->");
-
-@@ifobjc
-		      if (!is_public (expr, $3))
-			$$ = error_mark_node;
-		      else
-@@end_ifobjc
-			$$ = build_component_ref (expr, $3);
+		  $$ = build_component_ref (expr, $3);
 		}
 	| primary PLUSPLUS
 		{ $$ = build_unary_op (POSTINCREMENT_EXPR, $1, 0); }
@@ -734,6 +732,21 @@ primary:
 @@end_ifobjc
 	;
 
+/* This is the second argument to __builtin_offsetof.  We must have one
+   identifier, and beyond that we want to accept sub structure and sub
+   array references.  We return tree list where each element has
+   PURPOSE set for component refs or VALUE set for array refs.  We'll
+   turn this into something real inside build_offsetof.  */
+
+offsetof_member_designator:
+	  identifier
+		{ $$ = tree_cons ($1, NULL_TREE, NULL_TREE); }
+	| offsetof_member_designator '.' identifier
+		{ $$ = tree_cons ($3, NULL_TREE, $1); }
+	| offsetof_member_designator '[' expr ']'
+		{ $$ = tree_cons (NULL_TREE, $3, $1); }
+	;
+
 old_style_parm_decls:
 	/* empty */
 	| datadecls
@@ -3273,6 +3286,7 @@ static const struct resword reswords[] =
   { "__attribute",	RID_ATTRIBUTE,	0 },
   { "__attribute__",	RID_ATTRIBUTE,	0 },
   { "__builtin_choose_expr", RID_CHOOSE_EXPR, 0 },
+  { "__builtin_offsetof", RID_OFFSETOF, 0 },
   { "__builtin_types_compatible_p", RID_TYPES_COMPATIBLE_P, 0 },
   { "__builtin_va_arg",	RID_VA_ARG,	0 },
   { "__complex",	RID_COMPLEX,	0 },
@@ -3469,7 +3483,7 @@ static const short rid_to_yy[RID_MAX] =
   /* RID_FALSE */	0,
   /* RID_NAMESPACE */	0,
   /* RID_NEW */		0,
-  /* RID_OFFSETOF */    0,
+  /* RID_OFFSETOF */    OFFSETOF,
   /* RID_OPERATOR */	0,
   /* RID_THIS */	0,
   /* RID_THROW */	0,
Index: gcc/c-tree.h
===================================================================
RCS file: /cvs/gcc/gcc/gcc/c-tree.h,v
retrieving revision 1.146
diff -u -p -r1.146 c-tree.h
--- gcc/c-tree.h	30 May 2004 23:53:26 -0000	1.146
+++ gcc/c-tree.h	1 Jun 2004 15:03:46 -0000
@@ -258,6 +258,7 @@ extern tree build_asm_expr (tree, tree, 
 extern tree build_asm_stmt (tree, tree);
 extern tree c_convert_parm_for_inlining (tree, tree, tree, int);
 extern int c_types_compatible_p (tree, tree);
+extern tree build_offsetof (tree, tree);
 
 /* Set to 0 at beginning of a function definition, set to 1 if
    a return statement that specifies a return value is seen.  */
Index: gcc/c-typeck.c
===================================================================
RCS file: /cvs/gcc/gcc/gcc/c-typeck.c,v
retrieving revision 1.306
diff -u -p -r1.306 c-typeck.c
--- gcc/c-typeck.c	29 May 2004 18:40:27 -0000	1.306
+++ gcc/c-typeck.c	1 Jun 2004 15:03:47 -0000
@@ -1347,6 +1347,9 @@ build_component_ref (tree datum, tree co
   tree field = NULL;
   tree ref;
 
+  if (!objc_is_public (datum, component))
+    return error_mark_node;
+
   /* If DATUM is a COMPOUND_EXPR, move our reference inside it.
      Ensure that the arguments are not lvalues; otherwise,
      if the component is an array, it would wrongly decay to a pointer in
@@ -7114,3 +7117,30 @@ build_binary_op (enum tree_code code, tr
   }
 }
 
+/* Build the result of __builtin_offsetof.  TYPE is the first argument to
+   offsetof, i.e. a type.  LIST is a tree_list that encodes component and
+   array references; PURPOSE is set for the former and VALUE is set for
+   the later.  */
+
+tree
+build_offsetof (tree type, tree list)
+{
+  tree t;
+
+  /* Build "*(type *)0".  */
+  t = convert (build_pointer_type (type), null_pointer_node);
+  t = build_indirect_ref (t, "");
+
+  /* Build COMPONENT and ARRAY_REF expressions as needed.  */
+  for (list = nreverse (list); list ; list = TREE_CHAIN (list))
+    if (TREE_PURPOSE (list))
+      t = build_component_ref (t, TREE_PURPOSE (list));
+    else
+      t = build_array_ref (t, TREE_VALUE (list));
+
+  /* Finalize the offsetof expression.  For now all we need to do is take
+     the address of the expression we created, and cast that to an integer
+     type; this mirrors the traditional macro implementation of offsetof.  */
+  t = build_unary_op (ADDR_EXPR, t, 0);
+  return convert (size_type_node, t);
+}
Index: gcc/stub-objc.c
===================================================================
RCS file: /cvs/gcc/gcc/gcc/stub-objc.c,v
retrieving revision 2.1
diff -u -p -r2.1 stub-objc.c
--- gcc/stub-objc.c	25 Sep 2003 01:25:50 -0000	2.1
+++ gcc/stub-objc.c	1 Jun 2004 15:03:47 -0000
@@ -69,3 +69,8 @@ objc_message_selector (void)
   return 0;
 }
 
+int
+objc_is_public (tree expr ATTRIBUTE_UNUSED, tree identifier ATTRIBUTE_UNUSED)
+{
+  return 1;
+}
Index: gcc/cp/lex.c
===================================================================
RCS file: /cvs/gcc/gcc/gcc/cp/lex.c,v
retrieving revision 1.326
diff -u -p -r1.326 lex.c
--- gcc/cp/lex.c	9 Mar 2004 08:16:41 -0000	1.326
+++ gcc/cp/lex.c	1 Jun 2004 15:03:47 -0000
@@ -253,6 +253,7 @@ static const struct resword reswords[] =
   { "__asm__",		RID_ASM,	0 },
   { "__attribute",	RID_ATTRIBUTE,	0 },
   { "__attribute__",	RID_ATTRIBUTE,	0 },
+  { "__builtin_offsetof", RID_OFFSETOF, 0 },
   { "__builtin_va_arg",	RID_VA_ARG,	0 },
   { "__complex",	RID_COMPLEX,	0 },
   { "__complex__",	RID_COMPLEX,	0 },
@@ -266,8 +267,6 @@ static const struct resword reswords[] =
   { "__inline__",	RID_INLINE,	0 },
   { "__label__",	RID_LABEL,	0 },
   { "__null",		RID_NULL,	0 },
-  { "__offsetof",       RID_OFFSETOF,   0 },
-  { "__offsetof__",     RID_OFFSETOF,   0 },
   { "__real",		RID_REALPART,	0 },
   { "__real__",		RID_REALPART,	0 },
   { "__restrict",	RID_RESTRICT,	0 },
Index: gcc/cp/parser.c
===================================================================
RCS file: /cvs/gcc/gcc/gcc/cp/parser.c,v
retrieving revision 1.198
diff -u -p -r1.198 parser.c
--- gcc/cp/parser.c	1 Jun 2004 10:22:03 -0000	1.198
+++ gcc/cp/parser.c	1 Jun 2004 15:03:49 -0000
@@ -1232,9 +1232,6 @@ typedef struct cp_parser GTY(())
      been seen that makes the expression non-constant.  */
   bool non_integral_constant_expression_p;
 
-  /* TRUE if we are parsing the argument to "__offsetof__".  */
-  bool in_offsetof_p;
-
   /* TRUE if local variable names and `this' are forbidden in the
      current context.  */
   bool local_variables_forbidden_p;
@@ -1342,6 +1339,10 @@ static tree cp_parser_class_or_namespace
   (cp_parser *, bool, bool, bool, bool, bool);
 static tree cp_parser_postfix_expression
   (cp_parser *, bool);
+static tree cp_parser_postfix_open_square_expression
+  (cp_parser *, tree, bool);
+static tree cp_parser_postfix_dot_deref_expression
+  (cp_parser *, enum cpp_ttype, tree, bool, cp_id_kind *);
 static tree cp_parser_parenthesized_expression_list
   (cp_parser *, bool, bool *);
 static void cp_parser_pseudo_destructor_name
@@ -1398,6 +1399,8 @@ static tree cp_parser_expression
   (cp_parser *);
 static tree cp_parser_constant_expression
   (cp_parser *, bool, bool *);
+static tree cp_parser_builtin_offsetof
+  (cp_parser *);
 
 /* Statements [gram.stmt.stmt]  */
 
@@ -2324,9 +2327,6 @@ cp_parser_new (void)
   parser->allow_non_integral_constant_expression_p = false;
   parser->non_integral_constant_expression_p = false;
 
-  /* We are not parsing offsetof.  */
-  parser->in_offsetof_p = false;
-
   /* Local variable names are not forbidden.  */
   parser->local_variables_forbidden_p = false;
 
@@ -2603,27 +2603,7 @@ cp_parser_primary_expression (cp_parser 
 	  }
 
 	case RID_OFFSETOF:
-	  {
-	    tree expression;
-	    bool saved_in_offsetof_p;
-
-	    /* Consume the "__offsetof__" token.  */
-	    cp_lexer_consume_token (parser->lexer);
-	    /* Consume the opening `('.  */
-	    cp_parser_require (parser, CPP_OPEN_PAREN, "`('");
-	    /* Parse the parenthesized (almost) constant-expression.  */
-	    saved_in_offsetof_p = parser->in_offsetof_p;
-	    parser->in_offsetof_p = true;
-	    expression
-	      = cp_parser_constant_expression (parser,
-					       /*allow_non_constant_p=*/false,
-					       /*non_constant_p=*/NULL);
-	    parser->in_offsetof_p = saved_in_offsetof_p;
-	    /* Consume the closing ')'.  */
-	    cp_parser_require (parser, CPP_CLOSE_PAREN, "`)'");
-
-	    return expression;
-	  }
+	  return cp_parser_builtin_offsetof (parser);
 
 	default:
 	  cp_parser_error (parser, "expected primary-expression");
@@ -3520,9 +3500,6 @@ cp_parser_postfix_expression (cp_parser 
 	if (parser->integral_constant_expression_p
 	    && !dependent_type_p (type)
 	    && !INTEGRAL_OR_ENUMERATION_TYPE_P (type)
-	    /* A cast to pointer or reference type is allowed in the
-	       implementation of "offsetof".  */
-	    && !(parser->in_offsetof_p && POINTER_TYPE_P (type))
 	    && (cp_parser_non_integral_constant_expression 
 		(parser,
 		 "a cast to a type other than an integral or "
@@ -3765,29 +3742,11 @@ cp_parser_postfix_expression (cp_parser 
       switch (token->type)
 	{
 	case CPP_OPEN_SQUARE:
-	  /* postfix-expression [ expression ] */
-	  {
-	    tree index;
-
-	    /* Consume the `[' token.  */
-	    cp_lexer_consume_token (parser->lexer);
-	    /* Parse the index expression.  */
-	    index = cp_parser_expression (parser);
-	    /* Look for the closing `]'.  */
-	    cp_parser_require (parser, CPP_CLOSE_SQUARE, "`]'");
-
-	    /* Build the ARRAY_REF.  */
-	    postfix_expression
-	      = grok_array_decl (postfix_expression, index);
-	    idk = CP_ID_KIND_NONE;
-	    /* Array references are not permitted in
-	       constant-expressions (but they are allowed
-	       in offsetof).  */
-	    if (!parser->in_offsetof_p
-		&& cp_parser_non_integral_constant_expression
-		    (parser, "an array reference"))
-	      postfix_expression = error_mark_node;
-	  }
+	  postfix_expression
+	    = cp_parser_postfix_open_square_expression (parser,
+							postfix_expression,
+							false);
+	  idk = CP_ID_KIND_NONE;
 	  break;
 
 	case CPP_OPEN_PAREN:
@@ -3891,132 +3850,14 @@ cp_parser_postfix_expression (cp_parser 
 	     postfix-expression . pseudo-destructor-name
 	     postfix-expression -> template [opt] id-expression
 	     postfix-expression -> pseudo-destructor-name */
-	  {
-	    tree name;
-	    bool dependent_p;
-	    bool template_p;
-	    tree scope = NULL_TREE;
-	    enum cpp_ttype token_type = token->type;
-
-	    /* If this is a `->' operator, dereference the pointer.  */
-	    if (token->type == CPP_DEREF)
-	      postfix_expression = build_x_arrow (postfix_expression);
-	    /* Check to see whether or not the expression is
-	       type-dependent.  */
-	    dependent_p = type_dependent_expression_p (postfix_expression);
-	    /* The identifier following the `->' or `.' is not
-	       qualified.  */
-	    parser->scope = NULL_TREE;
-	    parser->qualifying_scope = NULL_TREE;
-	    parser->object_scope = NULL_TREE;
-	    idk = CP_ID_KIND_NONE;
-	    /* Enter the scope corresponding to the type of the object
-	       given by the POSTFIX_EXPRESSION.  */
-	    if (!dependent_p
-		&& TREE_TYPE (postfix_expression) != NULL_TREE)
-	      {
-		scope = TREE_TYPE (postfix_expression);
-		/* According to the standard, no expression should
-		   ever have reference type.  Unfortunately, we do not
-		   currently match the standard in this respect in
-		   that our internal representation of an expression
-		   may have reference type even when the standard says
-		   it does not.  Therefore, we have to manually obtain
-		   the underlying type here.  */
-		scope = non_reference (scope);
-		/* The type of the POSTFIX_EXPRESSION must be
-		   complete.  */
-		scope = complete_type_or_else (scope, NULL_TREE);
-		/* Let the name lookup machinery know that we are
-		   processing a class member access expression.  */
-		parser->context->object_type = scope;
-		/* If something went wrong, we want to be able to
-		   discern that case, as opposed to the case where
-		   there was no SCOPE due to the type of expression
-		   being dependent.  */
-		if (!scope)
-		  scope = error_mark_node;
-		/* If the SCOPE was erroneous, make the various
-		   semantic analysis functions exit quickly -- and
-		   without issuing additional error messages.  */
-		if (scope == error_mark_node)
-		  postfix_expression = error_mark_node;
-	      }
-
-	    /* Consume the `.' or `->' operator.  */
-	    cp_lexer_consume_token (parser->lexer);
-	    /* If the SCOPE is not a scalar type, we are looking at an
-	       ordinary class member access expression, rather than a
-	       pseudo-destructor-name.  */
-	    if (!scope || !SCALAR_TYPE_P (scope))
-	      {
-		template_p = cp_parser_optional_template_keyword (parser);
-		/* Parse the id-expression.  */
-		name = cp_parser_id_expression (parser,
-						template_p,
-						/*check_dependency_p=*/true,
-						/*template_p=*/NULL,
-						/*declarator_p=*/false);
-		/* In general, build a SCOPE_REF if the member name is
-		   qualified.  However, if the name was not dependent
-		   and has already been resolved; there is no need to
-		   build the SCOPE_REF.  For example;
-
-                     struct X { void f(); };
-                     template <typename T> void f(T* t) { t->X::f(); }
-
-                   Even though "t" is dependent, "X::f" is not and has
-		   been resolved to a BASELINK; there is no need to
-		   include scope information.  */
-
-		/* But we do need to remember that there was an explicit
-		   scope for virtual function calls.  */
-		if (parser->scope)
-		  idk = CP_ID_KIND_QUALIFIED;
-
-		if (name != error_mark_node
-		    && !BASELINK_P (name)
-		    && parser->scope)
-		  {
-		    name = build_nt (SCOPE_REF, parser->scope, name);
-		    parser->scope = NULL_TREE;
-		    parser->qualifying_scope = NULL_TREE;
-		    parser->object_scope = NULL_TREE;
-		  }
-		if (scope && name && BASELINK_P (name))
-		  adjust_result_of_qualified_name_lookup 
-		    (name, BINFO_TYPE (BASELINK_BINFO (name)), scope);
-		postfix_expression
-		  = finish_class_member_access_expr (postfix_expression, name);
-	      }
-	    /* Otherwise, try the pseudo-destructor-name production.  */
-	    else
-	      {
-		tree s = NULL_TREE;
-		tree type;
-
-		/* Parse the pseudo-destructor-name.  */
-		cp_parser_pseudo_destructor_name (parser, &s, &type);
-		/* Form the call.  */
-		postfix_expression
-		  = finish_pseudo_destructor_expr (postfix_expression,
-						   s, TREE_TYPE (type));
-	      }
+	
+	  /* Consume the `.' or `->' operator.  */
+	  cp_lexer_consume_token (parser->lexer);
 
-	    /* We no longer need to look up names in the scope of the
-	       object on the left-hand side of the `.' or `->'
-	       operator.  */
-	    parser->context->object_type = NULL_TREE;
-	    /* These operators may not appear in constant-expressions.  */
-	    if (/* The "->" operator is allowed in the implementation
-		   of "offsetof".  The "." operator may appear in the
-		   name of the member.  */
-		!parser->in_offsetof_p
-		&& (cp_parser_non_integral_constant_expression 
-		    (parser,
-		     token_type == CPP_DEREF ? "'->'" : "`.'")))
-	      postfix_expression = error_mark_node;
-	  }
+	  postfix_expression
+	    = cp_parser_postfix_dot_deref_expression (parser, token->type,
+						      postfix_expression,
+						      false, &idk);
 	  break;
 
 	case CPP_PLUS_PLUS:
@@ -4059,6 +3900,183 @@ cp_parser_postfix_expression (cp_parser 
   return error_mark_node;
 }
 
+/* A subroutine of cp_parser_postfix_expression that also gets hijacked
+   by cp_parser_builtin_offsetof.  We're looking for
+
+     postfix-expression [ expression ]
+
+   FOR_OFFSETOF is set if we're being called in that context, which
+   changes how we deal with integer constant expressions.  */
+
+static tree
+cp_parser_postfix_open_square_expression (cp_parser *parser,
+					  tree postfix_expression,
+					  bool for_offsetof)
+{
+  tree index;
+
+  /* Consume the `[' token.  */
+  cp_lexer_consume_token (parser->lexer);
+
+  /* Parse the index expression.  */
+  /* ??? For offsetof, there is a question of what to allow here.  If
+     offsetof is not being used in an integral constant expression context,
+     then we *could* get the right answer by computing the value at runtime.
+     If we are in an integral constant expression context, then we might
+     could accept any constant expression; hard to say without analysis.
+     Rather than open the barn door too wide right away, allow only integer
+     constant expresions here.  */
+  if (for_offsetof)
+    index = cp_parser_constant_expression (parser, false, NULL);
+  else
+    index = cp_parser_expression (parser);
+
+  /* Look for the closing `]'.  */
+  cp_parser_require (parser, CPP_CLOSE_SQUARE, "`]'");
+
+  /* Build the ARRAY_REF.  */
+  postfix_expression = grok_array_decl (postfix_expression, index);
+
+  /* When not doing offsetof, array references are not permitted in
+     constant-expressions.  */
+  if (!for_offsetof
+      && (cp_parser_non_integral_constant_expression
+	  (parser, "an array reference")))
+    postfix_expression = error_mark_node;
+
+  return postfix_expression;
+}
+
+/* A subroutine of cp_parser_postfix_expression that also gets hijacked
+   by cp_parser_builtin_offsetof.  We're looking for
+
+     postfix-expression . template [opt] id-expression
+     postfix-expression . pseudo-destructor-name
+     postfix-expression -> template [opt] id-expression
+     postfix-expression -> pseudo-destructor-name
+
+   FOR_OFFSETOF is set if we're being called in that context.  That sorta
+   limits what of the above we'll actually accept, but nevermind.
+   TOKEN_TYPE is the "." or "->" token, which will already have been
+   removed from the stream.  */
+
+static tree
+cp_parser_postfix_dot_deref_expression (cp_parser *parser,
+					enum cpp_ttype token_type,
+					tree postfix_expression,
+					bool for_offsetof, cp_id_kind *idk)
+{
+  tree name;
+  bool dependent_p;
+  bool template_p;
+  tree scope = NULL_TREE;
+
+  /* If this is a `->' operator, dereference the pointer.  */
+  if (token_type == CPP_DEREF)
+    postfix_expression = build_x_arrow (postfix_expression);
+  /* Check to see whether or not the expression is type-dependent.  */
+  dependent_p = type_dependent_expression_p (postfix_expression);
+  /* The identifier following the `->' or `.' is not qualified.  */
+  parser->scope = NULL_TREE;
+  parser->qualifying_scope = NULL_TREE;
+  parser->object_scope = NULL_TREE;
+  *idk = CP_ID_KIND_NONE;
+  /* Enter the scope corresponding to the type of the object
+     given by the POSTFIX_EXPRESSION.  */
+  if (!dependent_p && TREE_TYPE (postfix_expression) != NULL_TREE)
+    {
+      scope = TREE_TYPE (postfix_expression);
+      /* According to the standard, no expression should ever have
+	 reference type.  Unfortunately, we do not currently match
+	 the standard in this respect in that our internal representation
+	 of an expression may have reference type even when the standard
+	 says it does not.  Therefore, we have to manually obtain the
+	 underlying type here.  */
+      scope = non_reference (scope);
+      /* The type of the POSTFIX_EXPRESSION must be complete.  */
+      scope = complete_type_or_else (scope, NULL_TREE);
+      /* Let the name lookup machinery know that we are processing a
+	 class member access expression.  */
+      parser->context->object_type = scope;
+      /* If something went wrong, we want to be able to discern that case,
+	 as opposed to the case where there was no SCOPE due to the type
+	 of expression being dependent.  */
+      if (!scope)
+	scope = error_mark_node;
+      /* If the SCOPE was erroneous, make the various semantic analysis
+	 functions exit quickly -- and without issuing additional error
+	 messages.  */
+      if (scope == error_mark_node)
+	postfix_expression = error_mark_node;
+    }
+
+  /* If the SCOPE is not a scalar type, we are looking at an
+     ordinary class member access expression, rather than a
+     pseudo-destructor-name.  */
+  if (!scope || !SCALAR_TYPE_P (scope))
+    {
+      template_p = cp_parser_optional_template_keyword (parser);
+      /* Parse the id-expression.  */
+      name = cp_parser_id_expression (parser, template_p,
+				      /*check_dependency_p=*/true,
+				      /*template_p=*/NULL,
+				      /*declarator_p=*/false);
+      /* In general, build a SCOPE_REF if the member name is qualified.
+	 However, if the name was not dependent and has already been
+	 resolved; there is no need to build the SCOPE_REF.  For example;
+
+             struct X { void f(); };
+             template <typename T> void f(T* t) { t->X::f(); }
+
+	 Even though "t" is dependent, "X::f" is not and has been resolved
+	 to a BASELINK; there is no need to include scope information.  */
+
+      /* But we do need to remember that there was an explicit scope for
+	 virtual function calls.  */
+      if (parser->scope)
+	*idk = CP_ID_KIND_QUALIFIED;
+
+      if (name != error_mark_node && !BASELINK_P (name) && parser->scope)
+	{
+	  name = build_nt (SCOPE_REF, parser->scope, name);
+	  parser->scope = NULL_TREE;
+	  parser->qualifying_scope = NULL_TREE;
+	  parser->object_scope = NULL_TREE;
+	}
+      if (scope && name && BASELINK_P (name))
+	adjust_result_of_qualified_name_lookup 
+	  (name, BINFO_TYPE (BASELINK_BINFO (name)), scope);
+      postfix_expression
+	= finish_class_member_access_expr (postfix_expression, name);
+    }
+  /* Otherwise, try the pseudo-destructor-name production.  */
+  else
+    {
+      tree s = NULL_TREE;
+      tree type;
+
+      /* Parse the pseudo-destructor-name.  */
+      cp_parser_pseudo_destructor_name (parser, &s, &type);
+      /* Form the call.  */
+      postfix_expression
+	= finish_pseudo_destructor_expr (postfix_expression,
+					 s, TREE_TYPE (type));
+    }
+
+  /* We no longer need to look up names in the scope of the object on
+     the left-hand side of the `.' or `->' operator.  */
+  parser->context->object_type = NULL_TREE;
+
+  /* Outside of offsetof, these operators may not appear in
+     constant-expressions.  */
+  if (!for_offsetof
+      && (cp_parser_non_integral_constant_expression 
+	  (parser, token_type == CPP_DEREF ? "'->'" : "`.'")))
+    postfix_expression = error_mark_node;
+
+  return postfix_expression;
+}
+
 /* Parse a parenthesized expression-list.
 
    expression-list:
@@ -4420,10 +4438,7 @@ cp_parser_unary_expression (cp_parser *p
 	  break;
 
 	case ADDR_EXPR:
-	  /* The "&" operator is allowed in the implementation of
-	     "offsetof".  */
-	  if (!parser->in_offsetof_p)
-	    non_constant_p = "`&'";
+	  non_constant_p = "`&'";
 	  /* Fall through.  */
 	case BIT_NOT_EXPR:
 	  expression = build_x_unary_op (unary_operator, cast_expression);
@@ -5457,6 +5472,93 @@ cp_parser_constant_expression (cp_parser
   return expression;
 }
 
+/* Parse __builtin_offsetof.
+
+   offsetof-expression:
+     "__builtin_offsetof" "(" type-id "," offsetof-member-designator ")"
+
+   offsetof-member-designator:
+     id-expression
+     | offsetof-member-designator "." id-expression
+     | offsetof-member-designator "[" expression "]"
+*/
+
+static tree
+cp_parser_builtin_offsetof (cp_parser *parser)
+{
+  int save_ice_p, save_non_ice_p;
+  tree type, expr;
+  cp_id_kind dummy;
+
+  /* We're about to accept non-integral-constant things, but will
+     definitely yield an integral constant expression.  Save and
+     restore these values around our local parsing.  */
+  save_ice_p = parser->integral_constant_expression_p;
+  save_non_ice_p = parser->non_integral_constant_expression_p;
+
+  /* Consume the "__builtin_offsetof" token.  */
+  cp_lexer_consume_token (parser->lexer);
+  /* Consume the opening `('.  */
+  cp_parser_require (parser, CPP_OPEN_PAREN, "`('");
+  /* Parse the type-id.  */
+  type = cp_parser_type_id (parser);
+  /* Look for the `,'.  */
+  cp_parser_require (parser, CPP_COMMA, "`,'");
+
+  /* Build the (type *)null that begins the traditional offsetof macro.  */
+  expr = build_static_cast (build_pointer_type (type), null_pointer_node);
+
+  /* Parse the offsetof-member-designator.  We begin as if we saw "expr->".  */
+  expr = cp_parser_postfix_dot_deref_expression (parser, CPP_DEREF, expr,
+						 true, &dummy);
+  while (true)
+    {
+      cp_token *token = cp_lexer_peek_token (parser->lexer);
+      switch (token->type)
+	{
+	case CPP_OPEN_SQUARE:
+	  /* offsetof-member-designator "[" expression "]" */
+	  expr = cp_parser_postfix_open_square_expression (parser, expr, true);
+	  break;
+
+	case CPP_DOT:
+	  /* offsetof-member-designator "." identifier */
+	  cp_lexer_consume_token (parser->lexer);
+	  expr = cp_parser_postfix_dot_deref_expression (parser, CPP_DOT, expr,
+							 true, &dummy);
+	  break;
+
+	case CPP_CLOSE_PAREN:
+	  /* Consume the ")" token.  */
+	  cp_lexer_consume_token (parser->lexer);
+	  goto success;
+
+	default:
+	  /* Error.  We know the following require will fail, but
+	     that gives the proper error message.  */
+	  cp_parser_require (parser, CPP_CLOSE_PAREN, "`)'");
+	  cp_parser_skip_to_closing_parenthesis (parser, true, false, true);
+	  expr = error_mark_node;
+	  goto failure;
+	}
+    }
+
+ success:
+  /* We've finished the parsing, now finish with the semantics.  At present
+     we're just mirroring the traditional macro implementation.  Better
+     would be to do the lowering of the ADDR_EXPR to flat pointer arithmetic
+     here rather than in build_x_unary_op.  */
+  expr = build_reinterpret_cast (build_reference_type (char_type_node), expr);
+  expr = build_x_unary_op (ADDR_EXPR, expr);
+  expr = build_reinterpret_cast (size_type_node, expr);
+
+ failure:
+  parser->integral_constant_expression_p = save_ice_p;
+  parser->non_integral_constant_expression_p = save_non_ice_p;
+
+  return expr;
+}
+
 /* Statements [gram.stmt.stmt]  */
 
 /* Parse a statement.
Index: gcc/doc/extend.texi
===================================================================
RCS file: /cvs/gcc/gcc/gcc/doc/extend.texi,v
retrieving revision 1.193
diff -u -p -r1.193 extend.texi
--- gcc/doc/extend.texi	15 May 2004 10:02:07 -0000	1.193
+++ gcc/doc/extend.texi	1 Jun 2004 15:03:51 -0000
@@ -469,6 +469,7 @@ extensions, accepted by GCC in C89 mode 
 			 function.
 * Return Address::      Getting the return or frame address of a function.
 * Vector Extensions::   Using vector instructions through built-in functions.
+* Offsetof::            Special syntax for implementing @code{offsetof}.
 * Other Builtins::      Other built-in functions.
 * Target Builtins::     Built-in functions specific to particular targets.
 * Pragmas::             Pragmas accepted by GCC.
@@ -4704,6 +4705,33 @@ v4si f (v4si a, v4si b, v4si c)
 
 @end smallexample
 
+@node Offsetof
+@section Offsetof
+@findex __builtin_offsetof
+
+GCC implements for both C and C++ a syntactic extension to implement
+the @code{offsetof} macro.
+
+@smallexample
+primary:
+	"__builtin_offsetof" "(" @code{typename} "," offsetof_member_designator ")"
+
+offsetof_member_designator:
+	  @code{identifier}
+	| offsetof_member_designator "." @code{identifier}
+	| offsetof_member_designator "[" @code{expr} "]"
+@end smallexample
+
+This extension is sufficient such that
+
+@smallexample
+#define offsetof(@var{type}, @var{member})  __builtin_offsetof (@var{type}, @var{member})
+@end smallexample
+
+is a suitable definition of the @code{offsetof} macro.  In C++, @var{type}
+may be dependent.  In either case, @var{member} may consist of a single
+identifier, or a sequence of member accesses and array references.
+
 @node Other Builtins
 @section Other built-in functions provided by GCC
 @cindex built-in functions
@@ -7620,7 +7648,6 @@ Predefined Macros,cpp,The GNU C Preproce
                         method denoted by a @samp{->*} or @samp{.*} expression.
 * C++ Attributes::      Variable, function, and type attributes for C++ only.
 * Strong Using::      Strong using-directives for namespace composition.
-* Offsetof::            Special syntax for implementing @code{offsetof}.
 * Java Exceptions::     Tweaking exception handling to work with Java.
 * Deprecated Features:: Things will disappear from g++.
 * Backwards Compatibility:: Compatibilities with earlier definitions of C++.
@@ -8265,25 +8292,6 @@ int main()
 @}
 @end smallexample
 
-@node Offsetof
-@section Offsetof
-
-G++ uses a syntactic extension to implement the @code{offsetof} macro.
-
-In particular:
-
-@smallexample
-  __offsetof__ (expression)
-@end smallexample
-
-is equivalent to the parenthesized expression, except that the
-expression is considered an integral constant expression even if it
-contains certain operators that are not normally permitted in an
-integral constant expression.  Users should never use
-@code{__offsetof__} directly; the only valid use of
-@code{__offsetof__} is to implement the @code{offsetof} macro in
-@code{<stddef.h>}.
-
 @node Java Exceptions
 @section Java Exceptions
 
Index: gcc/ginclude/stddef.h
===================================================================
RCS file: /cvs/gcc/gcc/gcc/ginclude/stddef.h,v
retrieving revision 1.20
diff -u -p -r1.20 stddef.h
--- gcc/ginclude/stddef.h	16 Dec 2003 16:09:18 -0000	1.20
+++ gcc/ginclude/stddef.h	1 Jun 2004 15:03:51 -0000
@@ -1,4 +1,5 @@
-/* Copyright (C) 1989, 1997, 1998, 1999, 2000, 2002 Free Software Foundation, Inc.
+/* Copyright (C) 1989, 1997, 1998, 1999, 2000, 2002, 2004
+   Free Software Foundation, Inc.
 
 This file is part of GCC.
 
@@ -410,16 +411,8 @@ typedef __WINT_TYPE__ wint_t;
 #ifdef _STDDEF_H
 
 /* Offset of member MEMBER in a struct of type TYPE. */
-#ifndef __cplusplus
-#define offsetof(TYPE, MEMBER) ((size_t) &((TYPE *)0)->MEMBER)
-#else
-/* The cast to "char &" below avoids problems with user-defined
-   "operator &", which can appear in a POD type.  */
-#define offsetof(TYPE, MEMBER)				\
-  (__offsetof__ (reinterpret_cast <size_t>		\
-                 (&reinterpret_cast <char &>		\
-                  (static_cast<TYPE *> (0)->MEMBER))))
-#endif /* C++ */
+#define offsetof(TYPE, MEMBER) __builtin_offsetof (TYPE, MEMBER)
+
 #endif /* _STDDEF_H was defined this time */
 
 #endif /* !_STDDEF_H && !_STDDEF_H_ && !_ANSI_STDDEF_H && !__STDDEF_H__
Index: gcc/objc/objc-act.c
===================================================================
RCS file: /cvs/gcc/gcc/gcc/objc/objc-act.c,v
retrieving revision 1.215
diff -u -p -r1.215 objc-act.c
--- gcc/objc/objc-act.c	1 Jun 2004 07:39:58 -0000	1.215
+++ gcc/objc/objc-act.c	1 Jun 2004 15:03:52 -0000
@@ -6475,7 +6475,7 @@ is_private (tree decl)
 /* We have an instance variable reference;, check to see if it is public.  */
 
 int
-is_public (tree expr, tree identifier)
+objc_is_public (tree expr, tree identifier)
 {
   tree basetype = TREE_TYPE (expr);
   enum tree_code code = TREE_CODE (basetype);
Index: gcc/objc/objc-act.h
===================================================================
RCS file: /cvs/gcc/gcc/gcc/objc/objc-act.h,v
retrieving revision 1.21
diff -u -p -r1.21 objc-act.h
--- gcc/objc/objc-act.h	23 Mar 2004 23:47:50 -0000	1.21
+++ gcc/objc/objc-act.h	1 Jun 2004 15:03:52 -0000
@@ -52,7 +52,7 @@ tree objc_build_finally_epilogue (void);
 
 tree is_ivar (tree, tree);
 int is_private (tree);
-int is_public (tree, tree);
+int objc_is_public (tree, tree);
 tree add_instance_variable (tree, int, tree, tree, tree);
 tree objc_add_method (tree, tree, int);
 tree get_super_receiver (void);
@@ -126,7 +126,7 @@ tree build_encode_expr (tree);
 	 ? (TYPE)->type.context : NULL_TREE)
 #define SET_TYPE_PROTOCOL_LIST(TYPE, P) (TYPE_CHECK (TYPE)->type.context = (P))
 
-/* Set by `continue_class' and checked by `is_public'.  */
+/* Set by `continue_class' and checked by `objc_is_public'.  */
 
 #define TREE_STATIC_TEMPLATE(record_type) (TREE_PUBLIC (record_type))
 #define TYPED_OBJECT(type) \
Index: gcc/testsuite/g++.dg/template/dependent-expr4.C
===================================================================
RCS file: /cvs/gcc/gcc/gcc/testsuite/g++.dg/template/dependent-expr4.C,v
retrieving revision 1.1
diff -u -p -r1.1 dependent-expr4.C
--- gcc/testsuite/g++.dg/template/dependent-expr4.C	8 Jan 2004 11:57:53 -0000	1.1
+++ gcc/testsuite/g++.dg/template/dependent-expr4.C	1 Jun 2004 15:03:52 -0000
@@ -1,6 +1,7 @@
 // { dg-do compile }
 // Origin: jbrandmeyer at users dot sourceforge dot net
 // PR c++/12573: COMPONENT_REFs must be inspected for dependness.
+// Or, more specifically OFFSETOF.
 
 template <bool> struct S;
 
@@ -9,6 +10,6 @@ template <typename K> struct Y {
 };
 
 template <class T> struct Z {
-  S< (bool)(__offsetof__(&static_cast<Y<T>*>(0)->x) == 0) >
+  S< (bool)(__builtin_offsetof (Y<T>*, x) == 0) >
     s;
 };


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]