From 804fe3c4e68b9ab02f60ee33acfc325cfda76591 Mon Sep 17 00:00:00 2001
From: Emmanuel Briot <briot@adacore.com>
Date: Wed, 3 Aug 2011 09:30:45 +0000
Subject: [PATCH] prj-proc.adb, [...] (Environment): new type.

2011-08-03  Emmanuel Briot  <briot@adacore.com>

	* prj-proc.adb, prj.ads, makeutl.adb, makeutl.ads, prj-conf.adb,
	prj-tree.adb, prj-tree.ads (Environment): new type.

From-SVN: r177247
---
 gcc/ada/ChangeLog    |  5 +++++
 gcc/ada/makeutl.adb  |  4 ++--
 gcc/ada/makeutl.ads  |  4 ++--
 gcc/ada/prj-conf.adb |  3 ++-
 gcc/ada/prj-proc.adb |  8 +++-----
 gcc/ada/prj-tree.adb | 31 +++++++++++++++++++++++-----
 gcc/ada/prj-tree.ads | 48 +++++++++++++++++++++++++++++++-------------
 gcc/ada/prj.ads      |  2 ++
 8 files changed, 76 insertions(+), 29 deletions(-)

diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 111f819be81f..f415e5973ffb 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,8 @@
+2011-08-03  Emmanuel Briot  <briot@adacore.com>
+
+	* prj-proc.adb, prj.ads, makeutl.adb, makeutl.ads, prj-conf.adb,
+	prj-tree.adb, prj-tree.ads (Environment): new type.
+
 2011-08-03  Emmanuel Briot  <briot@adacore.com>
 
 	* prj-tree.ads: Remove unused variable.
diff --git a/gcc/ada/makeutl.adb b/gcc/ada/makeutl.adb
index 6673de198412..5f677ea699ee 100644
--- a/gcc/ada/makeutl.adb
+++ b/gcc/ada/makeutl.adb
@@ -701,7 +701,7 @@ package body Makeutl is
    ----------------------------
 
    function Is_External_Assignment
-     (Tree : Prj.Tree.Project_Node_Tree_Ref;
+     (Env  : Prj.Tree.Environment;
       Argv : String) return Boolean
    is
       Start     : Positive := 3;
@@ -724,7 +724,7 @@ package body Makeutl is
       end if;
 
       return Prj.Ext.Check
-        (Self        => Tree.External,
+        (Self        => Env.External,
          Declaration => Argv (Start .. Finish));
    end Is_External_Assignment;
 
diff --git a/gcc/ada/makeutl.ads b/gcc/ada/makeutl.ads
index 5ba084a00042..b1e5765c814d 100644
--- a/gcc/ada/makeutl.ads
+++ b/gcc/ada/makeutl.ads
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 S p e c                                  --
 --                                                                          --
---          Copyright (C) 2004-2010, Free Software Foundation, Inc.         --
+--          Copyright (C) 2004-2011, Free Software Foundation, Inc.         --
 --                                                                          --
 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
 -- terms of the  GNU General Public License as published  by the Free Soft- --
@@ -113,7 +113,7 @@ package Makeutl is
    --  if everything is still valid.
 
    function Is_External_Assignment
-     (Tree : Prj.Tree.Project_Node_Tree_Ref;
+     (Env  : Prj.Tree.Environment;
       Argv : String) return Boolean;
    --  Verify that an external assignment switch is syntactically correct
    --
diff --git a/gcc/ada/prj-conf.adb b/gcc/ada/prj-conf.adb
index 8a0a749a9cd8..de25dce40fba 100644
--- a/gcc/ada/prj-conf.adb
+++ b/gcc/ada/prj-conf.adb
@@ -573,6 +573,7 @@ package body Prj.Conf is
      (Project                    : Project_Id;
       Project_Tree               : Project_Tree_Ref;
       Project_Node_Tree          : Prj.Tree.Project_Node_Tree_Ref;
+      Env                        : Prj.Tree.Environment;
       Allow_Automatic_Generation : Boolean;
       Config_File_Name           : String := "";
       Autoconf_Specified         : Boolean;
@@ -1061,7 +1062,7 @@ package body Prj.Conf is
       Config_Project_Node : Project_Node_Id := Empty_Node;
 
    begin
-      pragma Assert (Prj.Env.Is_Initialized (Project_Node_Tree.Project_Path));
+      pragma Assert (Prj.Env.Is_Initialized (Env.Project_Path));
 
       Free (Config_File_Path);
       Config := No_Project;
diff --git a/gcc/ada/prj-proc.adb b/gcc/ada/prj-proc.adb
index 1a94e71d85bb..9c9c3b5f32c7 100644
--- a/gcc/ada/prj-proc.adb
+++ b/gcc/ada/prj-proc.adb
@@ -2814,8 +2814,7 @@ package body Prj.Proc is
                Project                => Project.Extends,
                Flags                  => Flags,
                From_Project_Node      => Extended_Project_Of
-                                          (Declaration_Node,
-                                           From_Project_Node_Tree),
+                 (Declaration_Node, From_Project_Node_Tree),
                From_Project_Node_Tree => From_Project_Node_Tree,
                Extended_By            => Project);
 
@@ -2824,11 +2823,10 @@ package body Prj.Proc is
                In_Tree                => In_Tree,
                Flags                  => Flags,
                From_Project_Node      => From_Project_Node,
-               Node_Tree => From_Project_Node_Tree,
+               Node_Tree              => From_Project_Node_Tree,
                Pkg                    => No_Package,
                Item                   => First_Declarative_Item_Of
-                                          (Declaration_Node,
-                                           From_Project_Node_Tree));
+                 (Declaration_Node, From_Project_Node_Tree));
 
             if Project.Extends /= No_Project then
                Process_Extended_Project;
diff --git a/gcc/ada/prj-tree.adb b/gcc/ada/prj-tree.adb
index 6fdb02e64aa8..6fa56ce975df 100644
--- a/gcc/ada/prj-tree.adb
+++ b/gcc/ada/prj-tree.adb
@@ -982,17 +982,26 @@ package body Prj.Tree is
    -- Initialize --
    ----------------
 
-   procedure Initialize (Tree : Project_Node_Tree_Ref) is
+   procedure Initialize
+     (Tree : Project_Node_Tree_Ref; Env : in out Environment) is
    begin
       Project_Node_Table.Init (Tree.Project_Nodes);
       Projects_Htable.Reset (Tree.Projects_HT);
+      Initialize (Env);
+   end Initialize;
 
+   ----------------
+   -- Initialize --
+   ----------------
+
+   procedure Initialize (Self : in out Environment) is
+   begin
       --  Do not reset the external references, in case we are reloading a
       --  project, since we want to preserve the current environment.
       --  But we still need to ensure that the external references are properly
       --  initialized.
 
-      Prj.Ext.Initialize (Tree.External);
+      Prj.Ext.Initialize (Self.External);
       --  Prj.Ext.Reset (Tree.External);
    end Initialize;
 
@@ -1000,17 +1009,29 @@ package body Prj.Tree is
    -- Free --
    ----------
 
-   procedure Free (Proj : in out Project_Node_Tree_Ref) is
+   procedure Free (Self : in out Environment) is
+   begin
+      Prj.Ext.Free (Self.External);
+      Free (Self.Project_Path);
+   end Free;
+
+   ----------
+   -- Free --
+   ----------
+
+   procedure Free
+     (Proj : in out Project_Node_Tree_Ref;
+      Env  : in out Environment)
+   is
       procedure Unchecked_Free is new Ada.Unchecked_Deallocation
         (Project_Node_Tree_Data, Project_Node_Tree_Ref);
    begin
       if Proj /= null then
          Project_Node_Table.Free (Proj.Project_Nodes);
          Projects_Htable.Reset (Proj.Projects_HT);
-         Prj.Ext.Free (Proj.External);
-         Free (Proj.Project_Path);
          Unchecked_Free (Proj);
       end if;
+      Free (Env);
    end Free;
 
    -------------------------------
diff --git a/gcc/ada/prj-tree.ads b/gcc/ada/prj-tree.ads
index 5bb123f7c56a..ae0d046366f0 100644
--- a/gcc/ada/prj-tree.ads
+++ b/gcc/ada/prj-tree.ads
@@ -36,6 +36,36 @@ with Prj.Ext;
 
 package Prj.Tree is
 
+   -----------------
+   -- Environment --
+   -----------------
+
+   type Environment is record
+      External : Prj.Ext.External_References;
+      --  External references are stored in this hash table (and manipulated
+      --  through subprograms in prj-ext.ads). External references are
+      --  project-tree specific so that one can load the same tree twice but
+      --  have two views of it, for instance.
+
+      Project_Path : aliased Prj.Env.Project_Search_Path;
+      --  The project path is tree specific, since we might want to load
+      --  simultaneously multiple projects, each with its own search path, in
+      --  particular when using different compilers with different default
+      --  search directories.
+   end record;
+   --  This record contains the context in which projects are parsed and
+   --  processed (finding importing project, resolving external values,...)
+
+   procedure Initialize (Self : in out Environment);
+   --  Initialize a new environment
+
+   procedure Free (Self : in out Environment);
+   --  Free the memory used by Self
+
+   -------------------
+   -- Project nodes --
+   -------------------
+
    type Project_Node_Tree_Data;
    type Project_Node_Tree_Ref is access all Project_Node_Tree_Data;
    --  Type to designate a project node tree, so that several project node
@@ -100,7 +130,8 @@ package Prj.Tree is
    pragma Inline (No);
    --  Return True if Node = Empty_Node
 
-   procedure Initialize (Tree : Project_Node_Tree_Ref);
+   procedure Initialize (Tree : Project_Node_Tree_Ref;
+                         Env : in out Environment);
    --  Initialize the Project File tree: empty the Project_Nodes table
    --  and reset the Projects_Htable.
 
@@ -1457,21 +1488,10 @@ package Prj.Tree is
    type Project_Node_Tree_Data is record
       Project_Nodes : Tree_Private_Part.Project_Node_Table.Instance;
       Projects_HT   : Tree_Private_Part.Projects_Htable.Instance;
-
-      External : Prj.Ext.External_References;
-      --  External references are stored in this hash table (and manipulated
-      --  through subprograms in prj-ext.ads). External references are
-      --  project-tree specific so that one can load the same tree twice but
-      --  have two views of it, for instance.
-
-      Project_Path : aliased Prj.Env.Project_Search_Path;
-      --  The project path is tree specific, since we might want to load
-      --  simultaneously multiple projects, each with its own search path, in
-      --  particular when using different compilers with different default
-      --  search directories.
    end record;
 
-   procedure Free (Proj : in out Project_Node_Tree_Ref);
+   procedure Free (Proj : in out Project_Node_Tree_Ref;
+                   Env : in out Environment);
    --  Free memory used by Prj
 
 private
diff --git a/gcc/ada/prj.ads b/gcc/ada/prj.ads
index db53aa081557..ebcc815c76e9 100644
--- a/gcc/ada/prj.ads
+++ b/gcc/ada/prj.ads
@@ -1321,6 +1321,8 @@ package Prj is
       case Qualifier is
          when Aggregate =>
             Aggregated_Projects : Aggregated_Project_List := null;
+            --  List of aggregated projects (which could themselves be
+            --  aggregate projects).
 
          when others =>
             null;
-- 
GitLab