diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index a6318b77ab47f6f180d61f177a832e37ad4b6a1a..0bc88d3cca6fe3bbc78d5d75aa1c56ebb44f581b 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,53 @@
+2005-12-05  Daniel Berlin  <dberlin@dberlin.org>
+	
+	* print-tree.c (print_node): Ditto.
+	* tree-dfa.c (add_referenced_var): Tag's don't have DECL_INITIAL.
+	* tree-dump.c (dequeue_and_dump): Check for decl_common structure
+	before accessing DECL_ARTIFICIAL. 
+	Handle new tag tree codes.
+	* tree-flow-inline.h (clear_call_clobbered): Update for tag
+	changes.
+	(unmodifiable_var_p): Ditto.
+	* tree-flow.h (mem_tag_kind): Remove.
+	(struct var_ann_d): Remove mem_tag_kind member.
+	* tree-gimple.c (is_gimple_reg): Tags are not gimple registers.
+	* tree-pretty-print.c (dump_generic_node): Handle memory tags.
+	* tree-ssa-alias.c (init_alias_info): Update for memory tag changes.
+	(group_aliases): Ditto.
+	(setup_pointers_and_addressables): Ditto.
+	(is_escape_site): Ditto.					  
+	(may_alias_p): Ditto.
+	(create_tag_raw): New function.
+	(create_memory_tag): Use it.
+	(dump_alias_info): Update for tags.
+	(may_be_aliased): Ditto.
+	(add_type_alias): Ditto.
+	(new_type_alias): Ditto.
+	(create_sft): Ditto.
+	(create_structure_vars): Ditto.
+	* tree-ssa-ccp.c (get_default_value): Ditto.
+	* tree-ssa-operands.c (get_expr_operands): Ditto.
+	(add_stmt_operand): Ditto.
+	(add_call_clobber_ops): Remove duplicated condition.
+	* tree-ssa.c (verify_flow_insensitive_alias_info): Update for
+	tags.
+	* tree-tailcall.c (suitable_for_tail_opt_p): Ditto.
+	* tree-vect-transform.c (vect_create_data_ref_ptr): Ditto.
+	* tree.c (init_ttree): Update structures for new tree codes.
+	(tree_code_size): Update sizes for new tree codes.
+	(make_node_stat): Don't try to set common things on minimal
+	structures.
+	(tree_node_structure): Update for tags.
+	(is_global_var): Ditto.
+	* tree.def: Add new tree codes.
+	* tree.h (MTAG_P): New macro.
+	(TREE_MEMORY_TAG_CHECK): Ditto.
+	(SSA_VAR_P): Update for tags.
+	(struct tree_memory_tag): New structure.
+	(MTAG_GLOBAL): New macro.
+	(union tree_node): Add memory tag member.
+	* treestruct.def (TS_MEMORY_TAG): New.
+	
 2005-12-05  Dale Johannesen  <dalej@apple.com>
 
 	* config/i386/xmmintrin.h (_MM_TRANSPOSE4_PS):  Fix to match
diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog
index b2b30097ac75e99c9e8176c56d2eafb2558cb29a..36642eb82809d8f56b7bc541e21e0dd2438b0b84 100644
--- a/gcc/cp/ChangeLog
+++ b/gcc/cp/ChangeLog
@@ -1,3 +1,8 @@
+2005-12-05  Daniel Berlin  <dberlin@dberlin.org>
+
+	* ptree.c (cxx_print_decl): Update to check for decl_common
+	structure.
+
 2005-12-02  Mark Mitchell  <mark@codesourcery.com>
 
 	PR c++/24173
diff --git a/gcc/cp/ptree.c b/gcc/cp/ptree.c
index 8a7ba94006360bf7aa17a2b08a003b5f8c7a3667..5d6651c53d81a2ba8fc0c1e644fc3b3a19e97704 100644
--- a/gcc/cp/ptree.c
+++ b/gcc/cp/ptree.c
@@ -41,7 +41,8 @@ cxx_print_decl (FILE *file, tree node, int indent)
       return;
     }
 
-  if (!DECL_LANG_SPECIFIC (node))
+  if (!CODE_CONTAINS_STRUCT (TREE_CODE (node), TS_DECL_COMMON)
+      || !DECL_LANG_SPECIFIC (node))
     return;
   indent_to (file, indent + 3);
   if (TREE_CODE (node) == FUNCTION_DECL
diff --git a/gcc/print-tree.c b/gcc/print-tree.c
index 9a8a5bb742aff77be44afc92d5aac7cfc3594ce5..d247835ea6d96e1c5d956df962bde30213e5abdb 100644
--- a/gcc/print-tree.c
+++ b/gcc/print-tree.c
@@ -314,18 +314,19 @@ print_node (FILE *file, const char *prefix, tree node, int indent)
   switch (TREE_CODE_CLASS (TREE_CODE (node)))
     {
     case tcc_declaration:
-      mode = DECL_MODE (node);
-
-      if (DECL_UNSIGNED (node))
-	fputs (" unsigned", file);
-      if (DECL_IGNORED_P (node))
-	fputs (" ignored", file);
-      if (DECL_ABSTRACT (node))
-	fputs (" abstract", file);      
-      if (DECL_EXTERNAL (node))
-	fputs (" external", file);
-      if (DECL_NONLOCAL (node))
-	fputs (" nonlocal", file);
+      if (CODE_CONTAINS_STRUCT (code, TS_DECL_COMMON))
+	{
+	  if (DECL_UNSIGNED (node))
+	    fputs (" unsigned", file);
+	  if (DECL_IGNORED_P (node))
+	    fputs (" ignored", file);
+	  if (DECL_ABSTRACT (node))
+	    fputs (" abstract", file);      
+	  if (DECL_EXTERNAL (node))
+	    fputs (" external", file);
+	  if (DECL_NONLOCAL (node))
+	    fputs (" nonlocal", file);
+	}
       if (CODE_CONTAINS_STRUCT (code, TS_DECL_WITH_VIS))
 	{
 	  if (DECL_WEAK (node))
@@ -385,66 +386,73 @@ print_node (FILE *file, const char *prefix, tree node, int indent)
 	    }
 	}
 
-      if (DECL_VIRTUAL_P (node))
-	fputs (" virtual", file);
+      if (CODE_CONTAINS_STRUCT (code, TS_DECL_COMMON))
+	{	  
+	  if (DECL_VIRTUAL_P (node))
+	    fputs (" virtual", file);
+	  if (DECL_PRESERVE_P (node))
+	    fputs (" preserve", file);	  
+	  if (DECL_LANG_FLAG_0 (node))
+	    fputs (" decl_0", file);
+	  if (DECL_LANG_FLAG_1 (node))
+	    fputs (" decl_1", file);
+	  if (DECL_LANG_FLAG_2 (node))
+	    fputs (" decl_2", file);
+	  if (DECL_LANG_FLAG_3 (node))
+	    fputs (" decl_3", file);
+	  if (DECL_LANG_FLAG_4 (node))
+	    fputs (" decl_4", file);
+	  if (DECL_LANG_FLAG_5 (node))
+	    fputs (" decl_5", file);
+	  if (DECL_LANG_FLAG_6 (node))
+	    fputs (" decl_6", file);
+	  if (DECL_LANG_FLAG_7 (node))
+	    fputs (" decl_7", file);
+	  
+	  mode = DECL_MODE (node);
+	  fprintf (file, " %s", GET_MODE_NAME (mode));
+	}
+
       if (CODE_CONTAINS_STRUCT (code, TS_DECL_WITH_VIS)  && DECL_DEFER_OUTPUT (node))
 	fputs (" defer-output", file);
 
-      if (DECL_PRESERVE_P (node))
-	fputs (" preserve", file);
-
-      if (DECL_LANG_FLAG_0 (node))
-	fputs (" decl_0", file);
-      if (DECL_LANG_FLAG_1 (node))
-	fputs (" decl_1", file);
-      if (DECL_LANG_FLAG_2 (node))
-	fputs (" decl_2", file);
-      if (DECL_LANG_FLAG_3 (node))
-	fputs (" decl_3", file);
-      if (DECL_LANG_FLAG_4 (node))
-	fputs (" decl_4", file);
-      if (DECL_LANG_FLAG_5 (node))
-	fputs (" decl_5", file);
-      if (DECL_LANG_FLAG_6 (node))
-	fputs (" decl_6", file);
-      if (DECL_LANG_FLAG_7 (node))
-	fputs (" decl_7", file);
 
-      fprintf (file, " %s", GET_MODE_NAME (mode));
       xloc = expand_location (DECL_SOURCE_LOCATION (node));
       fprintf (file, " file %s line %d", xloc.file, xloc.line);
 
-      print_node (file, "size", DECL_SIZE (node), indent + 4);
-      print_node (file, "unit size", DECL_SIZE_UNIT (node), indent + 4);
-
-      if (TREE_CODE (node) != FUNCTION_DECL
-	  || DECL_INLINE (node) || DECL_BUILT_IN (node))
-	indent_to (file, indent + 3);
-
-      if (TREE_CODE (node) != FUNCTION_DECL)
-	{
-	  if (DECL_USER_ALIGN (node))
-	    fprintf (file, " user");
-
-	  fprintf (file, " align %d", DECL_ALIGN (node));
-	  if (TREE_CODE (node) == FIELD_DECL)
-	    fprintf (file, " offset_align " HOST_WIDE_INT_PRINT_UNSIGNED,
-		     DECL_OFFSET_ALIGN (node));
-	}
-      else if (DECL_BUILT_IN (node))
-	{
-	  if (DECL_BUILT_IN_CLASS (node) == BUILT_IN_MD)
-	    fprintf (file, " built-in BUILT_IN_MD %d", DECL_FUNCTION_CODE (node));
-	  else
-	    fprintf (file, " built-in %s:%s",
-		     built_in_class_names[(int) DECL_BUILT_IN_CLASS (node)],
-		     built_in_names[(int) DECL_FUNCTION_CODE (node)]);
+      if (CODE_CONTAINS_STRUCT (code, TS_DECL_COMMON))
+	{	  
+	  print_node (file, "size", DECL_SIZE (node), indent + 4);
+	  print_node (file, "unit size", DECL_SIZE_UNIT (node), indent + 4);
+	  
+	  if (TREE_CODE (node) != FUNCTION_DECL
+	      || DECL_INLINE (node) || DECL_BUILT_IN (node))
+	    indent_to (file, indent + 3);
+	  
+	  if (TREE_CODE (node) != FUNCTION_DECL)
+	    {
+	      if (DECL_USER_ALIGN (node))
+		fprintf (file, " user");
+	      
+	      fprintf (file, " align %d", DECL_ALIGN (node));
+	      if (TREE_CODE (node) == FIELD_DECL)
+		fprintf (file, " offset_align " HOST_WIDE_INT_PRINT_UNSIGNED,
+			 DECL_OFFSET_ALIGN (node));
+	    }
+	  else if (DECL_BUILT_IN (node))
+	    {
+	      if (DECL_BUILT_IN_CLASS (node) == BUILT_IN_MD)
+		fprintf (file, " built-in BUILT_IN_MD %d", DECL_FUNCTION_CODE (node));
+	      else
+		fprintf (file, " built-in %s:%s",
+			 built_in_class_names[(int) DECL_BUILT_IN_CLASS (node)],
+			 built_in_names[(int) DECL_FUNCTION_CODE (node)]);
+	    }
+	  
+	  if (DECL_POINTER_ALIAS_SET_KNOWN_P (node))
+	    fprintf (file, " alias set " HOST_WIDE_INT_PRINT_DEC,
+		     DECL_POINTER_ALIAS_SET (node));
 	}
-
-      if (DECL_POINTER_ALIAS_SET_KNOWN_P (node))
-	fprintf (file, " alias set " HOST_WIDE_INT_PRINT_DEC,
-		 DECL_POINTER_ALIAS_SET (node));
-
       if (TREE_CODE (node) == FIELD_DECL)
 	{
 	  print_node (file, "offset", DECL_FIELD_OFFSET (node), indent + 4);
@@ -454,9 +462,12 @@ print_node (FILE *file, const char *prefix, tree node, int indent)
 
       print_node_brief (file, "context", DECL_CONTEXT (node), indent + 4);
 
-      print_node_brief (file, "attributes",
-			DECL_ATTRIBUTES (node), indent + 4);
-      
+      if (CODE_CONTAINS_STRUCT (code, TS_DECL_COMMON))	
+	{
+	  print_node_brief (file, "attributes",
+			    DECL_ATTRIBUTES (node), indent + 4);
+	  print_node_brief (file, "initial", DECL_INITIAL (node), indent + 4);
+	}
       if (CODE_CONTAINS_STRUCT (code, TS_DECL_WRTL))
 	{
 	  print_node_brief (file, "abstract_origin",
@@ -467,7 +478,6 @@ print_node (FILE *file, const char *prefix, tree node, int indent)
 	  print_node (file, "arguments", DECL_ARGUMENT_FLD (node), indent + 4);
 	  print_node (file, "result", DECL_RESULT_FLD (node), indent + 4);
 	}
-      print_node_brief (file, "initial", DECL_INITIAL (node), indent + 4);
 
       lang_hooks.print_decl (file, node, indent);
 
diff --git a/gcc/tree-dfa.c b/gcc/tree-dfa.c
index 9fc48d5cbe8c8fdb77941a46917763acb7aaf55f..3f89047714b2f79465709e8ebedac268fe4d6182 100644
--- a/gcc/tree-dfa.c
+++ b/gcc/tree-dfa.c
@@ -643,6 +643,10 @@ add_referenced_var (tree var, struct walk_state *walk_state)
       if (is_global_var (var))
 	mark_call_clobbered (var);
 
+      /* Tag's don't have DECL_INITIAL.  */
+      if (MTAG_P (var))
+	return;
+      
       /* Scan DECL_INITIAL for pointer variables as they may contain
 	 address arithmetic referencing the address of other
 	 variables.  */
diff --git a/gcc/tree-dump.c b/gcc/tree-dump.c
index 632687108e81a9afe0ca3c19918ea2e947e4f7c9..ea36129cdb687046a0c817be8f740bfaaf7ee637 100644
--- a/gcc/tree-dump.c
+++ b/gcc/tree-dump.c
@@ -343,7 +343,8 @@ dequeue_and_dump (dump_info_p di)
 	  di->column += 6 + strlen (filename) + 8;
 	}
       /* And any declaration can be compiler-generated.  */
-      if (DECL_ARTIFICIAL (t))
+      if (CODE_CONTAINS_STRUCT (TREE_CODE (t), TS_DECL_COMMON)
+	  && DECL_ARTIFICIAL (t))
 	dump_string_field (di, "note", "artificial");
       if (TREE_CHAIN (t) && !dump_flag (di, TDF_SLIM, NULL))
 	dump_child ("chan", TREE_CHAIN (t));
@@ -476,6 +477,11 @@ dequeue_and_dump (dump_info_p di)
     case CONST_DECL:
       dump_child ("cnst", DECL_INITIAL (t));
       break;
+      
+    case TYPE_MEMORY_TAG:
+    case NAME_MEMORY_TAG:
+    case STRUCT_FIELD_TAG:
+      break;
 
     case VAR_DECL:
     case PARM_DECL:
diff --git a/gcc/tree-flow-inline.h b/gcc/tree-flow-inline.h
index e1c19fc6dd4686310e6296890987665b1ce2f37e..ddfa77a7c0c8631794ed80d1f3f41e4efa6bd84e 100644
--- a/gcc/tree-flow-inline.h
+++ b/gcc/tree-flow-inline.h
@@ -845,13 +845,12 @@ is_call_clobbered (tree var)
 static inline void
 mark_call_clobbered (tree var)
 {
-  var_ann_t ann = var_ann (var);
   /* If VAR is a memory tag, then we need to consider it a global
      variable.  This is because the pointer that VAR represents has
      been found to point to either an arbitrary location or to a known
      location in global memory.  */
-  if (ann->mem_tag_kind != NOT_A_TAG && ann->mem_tag_kind != STRUCT_FIELD)
-    DECL_EXTERNAL (var) = 1;
+  if (MTAG_P (var) && TREE_CODE (var) != STRUCT_FIELD_TAG)
+    MTAG_GLOBAL (var) = 1;
   bitmap_set_bit (call_clobbered_vars, DECL_UID (var));
   ssa_call_clobbered_cache_valid = false;
   ssa_ro_call_cache_valid = false;
@@ -861,9 +860,8 @@ mark_call_clobbered (tree var)
 static inline void
 clear_call_clobbered (tree var)
 {
-  var_ann_t ann = var_ann (var);
-  if (ann->mem_tag_kind != NOT_A_TAG && ann->mem_tag_kind != STRUCT_FIELD)
-    DECL_EXTERNAL (var) = 0;
+  if (MTAG_P (var) && TREE_CODE (var) != STRUCT_FIELD_TAG)
+    MTAG_GLOBAL (var) = 0;
   bitmap_clear_bit (call_clobbered_vars, DECL_UID (var));
   ssa_call_clobbered_cache_valid = false;
   ssa_ro_call_cache_valid = false;
@@ -1404,6 +1402,10 @@ unmodifiable_var_p (tree var)
 {
   if (TREE_CODE (var) == SSA_NAME)
     var = SSA_NAME_VAR (var);
+
+  if (MTAG_P (var))
+    return TREE_READONLY (var) && (TREE_STATIC (var) || MTAG_GLOBAL (var));
+
   return TREE_READONLY (var) && (TREE_STATIC (var) || DECL_EXTERNAL (var));
 }
 
diff --git a/gcc/tree-flow.h b/gcc/tree-flow.h
index 4271d99009fc5471903817ad715500fe5e494753..6345d1ee3df858750d668061ed61e08562aa3c5e 100644
--- a/gcc/tree-flow.h
+++ b/gcc/tree-flow.h
@@ -137,28 +137,6 @@ enum need_phi_state {
   NEED_PHI_STATE_MAYBE
 };
 
-
-/* When computing aliasing information, we represent the memory pointed-to
-   by pointers with artificial variables called "memory tags" (MT).  There
-   are two kinds of tags: type and name.  Type tags (TMT) are used in
-   type-based alias analysis, they represent all the pointed-to locations
-   and variables of the same alias set class.  Name tags (NMT) are used in
-   flow-sensitive points-to alias analysis, they represent the variables
-   and memory locations pointed-to by a specific SSA_NAME pointer.  */
-enum mem_tag_kind {
-  /* This variable is not a memory tag.  */
-  NOT_A_TAG,
-
-  /* This variable is a type memory tag (TMT).  */
-  TYPE_TAG,
-
-  /* This variable is a name memory tag (NMT).  */
-  NAME_TAG,
-
-  /* This variable represents a structure field.  */
-  STRUCT_FIELD
-};
-
 struct subvar;
 typedef struct subvar *subvar_t;
 
@@ -189,9 +167,6 @@ struct var_ann_d GTY(())
   /* Used when building root_var structures in tree_ssa_live.[ch].  */
   unsigned root_var_processed : 1;
 
-  /* If nonzero, this variable is a memory tag.  */
-  ENUM_BITFIELD (mem_tag_kind) mem_tag_kind : 2;
-
   /* Nonzero if this variable is an alias tag that represents references to
      other variables (i.e., this variable appears in the MAY_ALIASES array
      of other variables).  */
diff --git a/gcc/tree-gimple.c b/gcc/tree-gimple.c
index 82bbf7acea418be0a5133c776be5cba4f1205717..3b70905cf84e90690a3bc16340d855505c78fb2b 100644
--- a/gcc/tree-gimple.c
+++ b/gcc/tree-gimple.c
@@ -266,11 +266,12 @@ is_gimple_reg_type (tree type)
 bool
 is_gimple_reg (tree t)
 {
-  var_ann_t ann;
-
   if (TREE_CODE (t) == SSA_NAME)
     t = SSA_NAME_VAR (t);
 
+  if (MTAG_P (t))
+    return false;
+
   if (!is_gimple_variable (t))
     return false;
 
@@ -305,12 +306,6 @@ is_gimple_reg (tree t)
   if (TREE_CODE (TREE_TYPE (t)) == COMPLEX_TYPE)
     return DECL_COMPLEX_GIMPLE_REG_P (t);
 
-  /* Some compiler temporaries are created to be used exclusively in
-     virtual operands (currently memory tags and sub-variables).
-     These variables should never be considered GIMPLE registers.  */
-  if (DECL_ARTIFICIAL (t) && (ann = var_ann (t)) != NULL)
-    return ann->mem_tag_kind == NOT_A_TAG;
-
   return true;
 }
 
diff --git a/gcc/tree-pretty-print.c b/gcc/tree-pretty-print.c
index 354a25a18189dd2c14ac436142bbd0aa67c60ec5..313e461dc8517e7816eed8303090d8c41181fe24 100644
--- a/gcc/tree-pretty-print.c
+++ b/gcc/tree-pretty-print.c
@@ -698,6 +698,9 @@ dump_generic_node (pretty_printer *buffer, tree node, int spc, int flags,
 	}
       break;
 
+    case TYPE_MEMORY_TAG:
+    case NAME_MEMORY_TAG:
+    case STRUCT_FIELD_TAG:
     case VAR_DECL:
     case PARM_DECL:
     case FIELD_DECL:
diff --git a/gcc/tree-ssa-alias.c b/gcc/tree-ssa-alias.c
index 84c522554b21c5147efdce1f0f34ab9e72f7851c..1a9c0060533821fa2cb09701c3487429b8b2bded 100644
--- a/gcc/tree-ssa-alias.c
+++ b/gcc/tree-ssa-alias.c
@@ -492,8 +492,8 @@ init_alias_info (void)
 	     a global variable, so we *don't* clear their call clobberedness
 	     just because they are tags, though we will clear it if they
 	     aren't for global variables.  */
-	  if (ann->mem_tag_kind == NAME_TAG 
-	      || ann->mem_tag_kind == TYPE_TAG 
+	  if (TREE_CODE (var) == NAME_MEMORY_TAG
+	      || TREE_CODE (var) == TYPE_MEMORY_TAG
 	      || !is_global_var (var))
 	    clear_call_clobbered (var);
 	}
@@ -1119,8 +1119,8 @@ group_aliases (struct alias_info *ai)
 	  tree alias = VARRAY_TREE (aliases, j);
 	  var_ann_t ann = var_ann (alias);
 
-	  if ((ann->mem_tag_kind == NOT_A_TAG 
-	       || ann->mem_tag_kind == STRUCT_FIELD)
+	  if ((!MTAG_P (alias)
+	       || TREE_CODE (alias) == STRUCT_FIELD_TAG)
 	      && ann->may_aliases)
 	    {
 	      tree new_alias;
@@ -1219,8 +1219,7 @@ setup_pointers_and_addressables (struct alias_info *ai)
          Structure fields, on the other hand, have to have some of this
          information processed for them, but it's pointless to mark them
          non-addressable (since they are fake variables anyway).  */
-      if (v_ann->mem_tag_kind != NOT_A_TAG
-	  && v_ann->mem_tag_kind != STRUCT_FIELD) 
+      if (MTAG_P (var) && TREE_CODE (var) != STRUCT_FIELD_TAG)
 	continue;
 
       /* Remove the ADDRESSABLE flag from every addressable variable whose
@@ -1464,7 +1463,6 @@ may_alias_p (tree ptr, HOST_WIDE_INT mem_alias_set,
 	     bool alias_set_only)
 {
   tree mem;
-  var_ann_t m_ann;
 
   alias_stats.alias_queries++;
   alias_stats.simple_queries++;
@@ -1498,9 +1496,7 @@ may_alias_p (tree ptr, HOST_WIDE_INT mem_alias_set,
       return false;
     }
 
-  m_ann = var_ann (mem);
-
-  gcc_assert (m_ann->mem_tag_kind == TYPE_TAG);
+  gcc_assert (TREE_CODE (mem) == TYPE_MEMORY_TAG);
 
   alias_stats.tbaa_queries++;
 
@@ -1729,6 +1725,31 @@ is_escape_site (tree stmt, struct alias_info *ai)
   return false;
 }
 
+/* Create a new memory tag of type TYPE.
+   Does NOT push it into the current binding.  */
+
+static tree
+create_tag_raw (enum tree_code code, tree type, const char *prefix)
+{
+  tree tmp_var;
+  tree new_type;
+
+  /* Make the type of the variable writable.  */
+  new_type = build_type_variant (type, 0, 0);
+  TYPE_ATTRIBUTES (new_type) = TYPE_ATTRIBUTES (type);
+
+  tmp_var = build_decl (code, create_tmp_var_name (prefix),
+			type);
+  /* Make the variable writable.  */
+  TREE_READONLY (tmp_var) = 0;
+
+  /* It doesn't start out global.  */
+  MTAG_GLOBAL (tmp_var) = 0;
+  TREE_STATIC (tmp_var) = 0;
+  TREE_USED (tmp_var) = 1;
+
+  return tmp_var;
+}
 
 /* Create a new memory tag of type TYPE.  If IS_TYPE_TAG is true, the tag
    is considered to represent all the pointers whose pointed-to types are
@@ -1739,7 +1760,8 @@ static tree
 create_memory_tag (tree type, bool is_type_tag)
 {
   var_ann_t ann;
-  tree tag = create_tmp_var_raw (type, (is_type_tag) ? "TMT" : "NMT");
+  tree tag = create_tag_raw (is_type_tag ? TYPE_MEMORY_TAG : NAME_MEMORY_TAG,
+			     type, (is_type_tag) ? "TMT" : "NMT");
 
   /* By default, memory tags are local variables.  Alias analysis will
      determine whether they should be considered globals.  */
@@ -1749,7 +1771,6 @@ create_memory_tag (tree type, bool is_type_tag)
   TREE_ADDRESSABLE (tag) = 1;
 
   ann = get_var_ann (tag);
-  ann->mem_tag_kind = (is_type_tag) ? TYPE_TAG : NAME_TAG;
   ann->type_mem_tag = NULL_TREE;
 
   /* Add the tag to the symbol table.  */
@@ -1942,8 +1963,7 @@ dump_alias_info (FILE *file)
   
   FOR_EACH_REFERENCED_VAR (var, rvi)
     {
-      var_ann_t ann = var_ann (var);
-      if (ann->mem_tag_kind == TYPE_TAG)
+      if (TREE_CODE (var) == TYPE_MEMORY_TAG)
 	dump_variable (file, var);
     }
 
@@ -1969,8 +1989,7 @@ dump_alias_info (FILE *file)
   
   FOR_EACH_REFERENCED_VAR (var, rvi)
     {
-      var_ann_t ann = var_ann (var);
-      if (ann->mem_tag_kind == NAME_TAG)
+      if (TREE_CODE (var) == NAME_MEMORY_TAG)
 	dump_variable (file, var);
     }
 
@@ -2173,7 +2192,12 @@ may_be_aliased (tree var)
 
   /* Globally visible variables can have their addresses taken by other
      translation units.  */
-  if (DECL_EXTERNAL (var) || TREE_PUBLIC (var))
+
+  if (MTAG_P (var)
+      && (MTAG_GLOBAL (var) || TREE_PUBLIC (var)))
+    return true;
+  else if (!MTAG_P (var)
+      && (DECL_EXTERNAL (var) || TREE_PUBLIC (var)))
     return true;
 
   /* Automatic variables can't have their addresses escape any other way.
@@ -2280,7 +2304,7 @@ add_type_alias (tree ptr, tree var)
 found_tag:
   /* If VAR is not already PTR's type tag, add it to the may-alias set
      for PTR's type tag.  */
-  gcc_assert (var_ann (var)->type_mem_tag == NOT_A_TAG);
+  gcc_assert (!MTAG_P (var_ann (var)->type_mem_tag));
   tag = ann->type_mem_tag;
 
   /* If VAR has subvars, add the subvars to the tag instead of the
@@ -2333,7 +2357,7 @@ new_type_alias (tree ptr, tree var)
   subvar_t svars;
 
   gcc_assert (p_ann->type_mem_tag == NULL_TREE);
-  gcc_assert (v_ann->mem_tag_kind == NOT_A_TAG);
+  gcc_assert (!MTAG_P (var));
 
   /* Add VAR to the may-alias set of PTR's new type tag.  If VAR has
      subvars, add the subvars to the tag instead of the actual var.  */
@@ -2361,7 +2385,7 @@ new_type_alias (tree ptr, tree var)
 	{
 	  tree ali = VARRAY_TREE (aliases, 0);
 
-	  if (get_var_ann (ali)->mem_tag_kind == TYPE_TAG)
+	  if (TREE_CODE (ali) == TYPE_MEMORY_TAG)
 	    {
 	      p_ann->type_mem_tag = ali;
 	      return;
@@ -2495,19 +2519,18 @@ static tree
 create_sft (tree var, tree field)
 {
   var_ann_t ann;
-  tree subvar = create_tmp_var_raw (TREE_TYPE (field), "SFT");
+  tree subvar = create_tag_raw (STRUCT_FIELD_TAG, TREE_TYPE (field), "SFT");
 
   /* We need to copy the various flags from VAR to SUBVAR, so that
      they are is_global_var iff the original variable was.  */
   DECL_CONTEXT (subvar) = DECL_CONTEXT (var);
-  DECL_EXTERNAL (subvar) = DECL_EXTERNAL (var);
+  MTAG_GLOBAL (subvar) = DECL_EXTERNAL (var);
   TREE_PUBLIC  (subvar) = TREE_PUBLIC (var);
   TREE_STATIC (subvar) = TREE_STATIC (var);
   TREE_READONLY (subvar) = TREE_READONLY (var);
 
   /* Add the new variable to REFERENCED_VARS.  */
   ann = get_var_ann (subvar);
-  ann->mem_tag_kind = STRUCT_FIELD; 
   ann->type_mem_tag = NULL;  	
   add_referenced_tmp_var (subvar);
 
@@ -2812,7 +2835,7 @@ create_structure_vars (void)
       if (var 	  
 	  && DECL_SIZE (var)
 	  && var_can_have_subvars (var)
-	  && var_ann (var)->mem_tag_kind == NOT_A_TAG
+	  && !MTAG_P (var)
 	  && TREE_CODE (DECL_SIZE (var)) == INTEGER_CST)
 	create_overlap_variables_for (var);
     }
diff --git a/gcc/tree-ssa-ccp.c b/gcc/tree-ssa-ccp.c
index 133d00a709035421e511a98b35311c61ee67eef7..08200ff0c580505e9299a102f2288eecdecb880f 100644
--- a/gcc/tree-ssa-ccp.c
+++ b/gcc/tree-ssa-ccp.c
@@ -342,6 +342,7 @@ get_default_value (tree var)
     }
   else if (TREE_STATIC (sym)
 	   && TREE_READONLY (sym)
+	   && !MTAG_P (sym)
 	   && DECL_INITIAL (sym)
 	   && ccp_decl_initial_min_invariant (DECL_INITIAL (sym)))
     {
diff --git a/gcc/tree-ssa-operands.c b/gcc/tree-ssa-operands.c
index d6c8ccb3f7d27b243e7a89a4fb62ea8437be5757..b9873314079fc87ae27295cc95d367bc90ed699d 100644
--- a/gcc/tree-ssa-operands.c
+++ b/gcc/tree-ssa-operands.c
@@ -1091,6 +1091,9 @@ get_expr_operands (tree stmt, tree *expr_p, int flags)
       return;
 
     case SSA_NAME:
+    case STRUCT_FIELD_TAG:
+    case TYPE_MEMORY_TAG:
+    case NAME_MEMORY_TAG:
     case VAR_DECL:
     case PARM_DECL:
     case RESULT_DECL:
@@ -1679,8 +1682,8 @@ add_stmt_operand (tree *var_p, stmt_ann_t s_ann, int flags)
 		{
 		  /* Only regular variables or struct fields may get a
 		     V_MUST_DEF operand.  */
-		  gcc_assert (v_ann->mem_tag_kind == NOT_A_TAG 
-			      || v_ann->mem_tag_kind == STRUCT_FIELD);
+		  gcc_assert (!MTAG_P (var)
+			      || TREE_CODE (var) == STRUCT_FIELD_TAG);
 		  /* V_MUST_DEF for non-aliased, non-GIMPLE register 
 		    variable definitions.  */
 		  append_v_must_def (var);
diff --git a/gcc/tree-ssa.c b/gcc/tree-ssa.c
index 7b24c594a5cc6710abc58a67bfc2d335b9802d21..4c683f1b0f6416eace42506649b1dedb77b07c76 100644
--- a/gcc/tree-ssa.c
+++ b/gcc/tree-ssa.c
@@ -406,7 +406,7 @@ verify_flow_insensitive_alias_info (void)
       var_ann_t ann;
       ann = var_ann (var);
 
-      if (ann->mem_tag_kind == NOT_A_TAG
+      if (!MTAG_P (var)
 	  && ann->is_alias_tag
 	  && !bitmap_bit_p (visited, DECL_UID (var)))
 	{
diff --git a/gcc/tree-tailcall.c b/gcc/tree-tailcall.c
index ce5af15ef1c7c0838750856654bf8b11f4f261b1..c5a25270829581975c42803547174eb1ee69baff 100644
--- a/gcc/tree-tailcall.c
+++ b/gcc/tree-tailcall.c
@@ -144,9 +144,8 @@ suitable_for_tail_opt_p (void)
   FOR_EACH_REFERENCED_VAR (var, rvi)
     {
 
-      if (!(TREE_STATIC (var) || DECL_EXTERNAL (var))
-	  && (var_ann (var)->mem_tag_kind == NOT_A_TAG
-	      || var_ann (var)->mem_tag_kind == STRUCT_FIELD)
+      if (!is_global_var (var)
+	  && (!MTAG_P (var) || TREE_CODE (var) == STRUCT_FIELD_TAG)
 	  && is_call_clobbered (var))
 	return false;
     }
diff --git a/gcc/tree-vect-transform.c b/gcc/tree-vect-transform.c
index bdf26173288ad13ebb6f90f5e0d0ca2524538287..0d56efb50f5be5a03868243cb7c5bd1713167d33 100644
--- a/gcc/tree-vect-transform.c
+++ b/gcc/tree-vect-transform.c
@@ -301,7 +301,7 @@ vect_create_data_ref_ptr (tree stmt,
 
   /* If tag is a variable (and NOT_A_TAG) than a new type alias
      tag must be created with tag added to its may alias list.  */
-  if (var_ann (tag)->mem_tag_kind == NOT_A_TAG)
+  if (!MTAG_P (tag))
     new_type_alias (vect_ptr, tag);
   else
     var_ann (vect_ptr)->type_mem_tag = tag;
diff --git a/gcc/tree.c b/gcc/tree.c
index 6a97e4109940f35a128f3794022aa1fb1eb2772f..324e83301f5fc81adc359d541c7ea63e2eb98b58 100644
--- a/gcc/tree.c
+++ b/gcc/tree.c
@@ -230,6 +230,13 @@ init_ttree (void)
   tree_contains_struct[TRANSLATION_UNIT_DECL][TS_DECL_MINIMAL] = 1;
   tree_contains_struct[LABEL_DECL][TS_DECL_MINIMAL] = 1;
   tree_contains_struct[FIELD_DECL][TS_DECL_MINIMAL] = 1;
+  tree_contains_struct[STRUCT_FIELD_TAG][TS_DECL_MINIMAL] = 1;
+  tree_contains_struct[NAME_MEMORY_TAG][TS_DECL_MINIMAL] = 1;
+  tree_contains_struct[TYPE_MEMORY_TAG][TS_DECL_MINIMAL] = 1;
+
+  tree_contains_struct[STRUCT_FIELD_TAG][TS_MEMORY_TAG] = 1;
+  tree_contains_struct[NAME_MEMORY_TAG][TS_MEMORY_TAG] = 1;
+  tree_contains_struct[TYPE_MEMORY_TAG][TS_MEMORY_TAG] = 1;
 
   tree_contains_struct[VAR_DECL][TS_DECL_WITH_VIS] = 1;
   tree_contains_struct[FUNCTION_DECL][TS_DECL_WITH_VIS] = 1;
@@ -288,6 +295,10 @@ tree_code_size (enum tree_code code)
 	    return sizeof (struct tree_type_decl);
 	  case FUNCTION_DECL:
 	    return sizeof (struct tree_function_decl);
+	  case NAME_MEMORY_TAG:
+	  case TYPE_MEMORY_TAG:
+	  case STRUCT_FIELD_TAG:
+	    return sizeof (struct tree_memory_tag);
 	  default:
 	    return sizeof (struct tree_decl_non_common);
 	  }
@@ -479,13 +490,16 @@ make_node_stat (enum tree_code code MEM_STAT_DECL)
       break;
 
     case tcc_declaration:
-      if (code != FUNCTION_DECL)
-	DECL_ALIGN (t) = 1;
-      DECL_USER_ALIGN (t) = 0;
       if (CODE_CONTAINS_STRUCT (code, TS_DECL_WITH_VIS))
 	DECL_IN_SYSTEM_HEADER (t) = in_system_header;
-      /* We have not yet computed the alias set for this declaration.  */
-      DECL_POINTER_ALIAS_SET (t) = -1;
+      if (CODE_CONTAINS_STRUCT (code, TS_DECL_COMMON))
+	{
+	  if (code != FUNCTION_DECL)
+	    DECL_ALIGN (t) = 1;
+	  DECL_USER_ALIGN (t) = 0;	  
+	  /* We have not yet computed the alias set for this declaration.  */
+	  DECL_POINTER_ALIAS_SET (t) = -1;
+	}
       DECL_SOURCE_LOCATION (t) = input_location;
       DECL_UID (t) = next_decl_uid++;
 
@@ -1979,6 +1993,10 @@ tree_node_structure (tree t)
 	    return TS_TYPE_DECL;
 	  case FUNCTION_DECL:
 	    return TS_FUNCTION_DECL;
+	  case TYPE_MEMORY_TAG:
+	  case NAME_MEMORY_TAG:
+	  case STRUCT_FIELD_TAG:
+	    return TS_MEMORY_TAG;
 	  default:
 	    return TS_DECL_NON_COMMON;
 	  }
@@ -6630,7 +6648,10 @@ in_array_bounds_p (tree ref)
 bool
 is_global_var (tree t)
 {
-  return (TREE_STATIC (t) || DECL_EXTERNAL (t));
+  if (MTAG_P (t))
+    return (TREE_STATIC (t) || MTAG_GLOBAL (t));
+  else
+    return (TREE_STATIC (t) || DECL_EXTERNAL (t));
 }
 
 /* Return true if T (assumed to be a DECL) must be assigned a memory
diff --git a/gcc/tree.def b/gcc/tree.def
index 84d76c46533033bb9a140e11b3e6c8a593447439..66692b4016867f2df137e9e2e3c7d909a8a91d4f 100644
--- a/gcc/tree.def
+++ b/gcc/tree.def
@@ -358,6 +358,12 @@ DEFTREECODE (PARM_DECL, "parm_decl", tcc_declaration, 0)
 DEFTREECODE (TYPE_DECL, "type_decl", tcc_declaration, 0)
 DEFTREECODE (RESULT_DECL, "result_decl", tcc_declaration, 0)
 
+/* Memory tags used in tree-ssa to represent memory locations in
+   virtual SSA.  */
+DEFTREECODE (STRUCT_FIELD_TAG, "struct_field_tag", tcc_declaration, 0)
+DEFTREECODE (NAME_MEMORY_TAG, "name_memory_tag", tcc_declaration, 0)
+DEFTREECODE (TYPE_MEMORY_TAG, "type_memory_tag", tcc_declaration, 0)
+
 /* A namespace declaration.  Namespaces appear in DECL_CONTEXT of other
    _DECLs, providing a hierarchy of names.  */
 DEFTREECODE (NAMESPACE_DECL, "namespace_decl", tcc_declaration, 0)
diff --git a/gcc/tree.h b/gcc/tree.h
index 6946dd450a8ea94cf83ef6a84a42ec5722c6d4fe..99c18f4e1a685f6b401cc2f901c6fc78e33d611d 100644
--- a/gcc/tree.h
+++ b/gcc/tree.h
@@ -100,6 +100,14 @@ extern const enum tree_code_class tree_code_type[];
 #define DECL_P(CODE)\
         (TREE_CODE_CLASS (TREE_CODE (CODE)) == tcc_declaration)
 
+/* Nonzero if CODE represents a memory tag.  */
+
+#define MTAG_P(CODE) \
+  (TREE_CODE (CODE) == STRUCT_FIELD_TAG		\
+   || TREE_CODE (CODE) == NAME_MEMORY_TAG	\
+   || TREE_CODE (CODE) == TYPE_MEMORY_TAG)
+        
+
 /* Nonzero if DECL represents a VAR_DECL or FUNCTION_DECL.  */
 
 #define VAR_OR_FUNCTION_DECL_P(DECL)\
@@ -692,6 +700,7 @@ extern void tree_operand_check_failed (int, enum tree_code,
 
 #define TYPE_CHECK(T)		TREE_CLASS_CHECK (T, tcc_type)
 #define DECL_MINIMAL_CHECK(T)   CONTAINS_STRUCT_CHECK (T, TS_DECL_MINIMAL)
+#define TREE_MEMORY_TAG_CHECK(T)       CONTAINS_STRUCT_CHECK (T, TS_MEMORY_TAG)
 #define DECL_COMMON_CHECK(T)    CONTAINS_STRUCT_CHECK (T, TS_DECL_COMMON)
 #define DECL_WRTL_CHECK(T)      CONTAINS_STRUCT_CHECK (T, TS_DECL_WRTL)
 #define DECL_WITH_VIS_CHECK(T)  CONTAINS_STRUCT_CHECK (T, TS_DECL_WITH_VIS)
@@ -1972,14 +1981,16 @@ struct tree_binfo GTY (())
 /* Define fields and accessors for nodes representing declared names.  */
 
 /* Nonzero if DECL represents a variable for the SSA passes.  */
-#define SSA_VAR_P(DECL) \
-	(TREE_CODE (DECL) == VAR_DECL	\
-	 || TREE_CODE (DECL) == PARM_DECL \
-	 || TREE_CODE (DECL) == RESULT_DECL \
-	 || (TREE_CODE (DECL) == SSA_NAME \
-	     && (TREE_CODE (SSA_NAME_VAR (DECL)) == VAR_DECL \
-		 || TREE_CODE (SSA_NAME_VAR (DECL)) == PARM_DECL \
-		 || TREE_CODE (SSA_NAME_VAR (DECL)) == RESULT_DECL)))
+#define SSA_VAR_P(DECL)							\
+	(TREE_CODE (DECL) == VAR_DECL					\
+	 || TREE_CODE (DECL) == PARM_DECL				\
+	 || TREE_CODE (DECL) == RESULT_DECL				\
+	 || MTAG_P (DECL)						\
+	 || (TREE_CODE (DECL) == SSA_NAME				\
+	     && (TREE_CODE (SSA_NAME_VAR (DECL)) == VAR_DECL		\
+		 || TREE_CODE (SSA_NAME_VAR (DECL)) == PARM_DECL	\
+		 || TREE_CODE (SSA_NAME_VAR (DECL)) == RESULT_DECL	\
+		 || MTAG_P (SSA_NAME_VAR (DECL)))))
 
 
 
@@ -2038,6 +2049,24 @@ struct tree_decl_minimal GTY(())
   tree context;
 };
 
+/* When computing aliasing information, we represent the memory pointed-to
+   by pointers with artificial variables called "memory tags" (MT).  There
+   are two kinds of tags: type and name.  Type tags (TMT) are used in
+   type-based alias analysis, they represent all the pointed-to locations
+   and variables of the same alias set class.  Name tags (NMT) are used in
+   flow-sensitive points-to alias analysis, they represent the variables
+   and memory locations pointed-to by a specific SSA_NAME pointer.  */
+
+struct tree_memory_tag GTY(())
+{
+  struct tree_decl_minimal common;
+  tree parent_var;
+  unsigned int is_global:1;
+};
+
+#define MTAG_GLOBAL(NODE) (TREE_MEMORY_TAG_CHECK (NODE)->mtag.is_global)
+#define SFT_PARENT_VAR(NODE) (STRUCT_FIELD_TAG_CHECK (NODE)->mtag.parent_var)
+
 /* For any sort of a ..._DECL node, this points to the original (abstract)
    decl node which this decl is an instance of, or else it is NULL indicating
    that this decl is not an instance of some other decl.  For example,
@@ -2834,6 +2863,7 @@ union tree_node GTY ((ptr_alias (union lang_tree_node),
   struct tree_statement_list GTY ((tag ("TS_STATEMENT_LIST"))) stmt_list;
   struct tree_value_handle GTY ((tag ("TS_VALUE_HANDLE"))) value_handle;
   struct tree_constructor GTY ((tag ("TS_CONSTRUCTOR"))) constructor;
+  struct tree_memory_tag GTY ((tag ("TS_MEMORY_TAG"))) mtag;
 };
 
 /* Standard named or nameless data types of the C compiler.  */
diff --git a/gcc/treestruct.def b/gcc/treestruct.def
index 66ffc1b1c5725e8639b6998631b0929e3fd9dd90..e8d016a1866f889077b856c82d567b3ec2d9ca66 100644
--- a/gcc/treestruct.def
+++ b/gcc/treestruct.def
@@ -59,3 +59,4 @@ DEFTREESTRUCT(TS_BINFO, "binfo")
 DEFTREESTRUCT(TS_STATEMENT_LIST, "statement list")
 DEFTREESTRUCT(TS_VALUE_HANDLE, "value handle")
 DEFTREESTRUCT(TS_CONSTRUCTOR, "constructor")
+DEFTREESTRUCT(TS_MEMORY_TAG, "memory tag")