diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 191ef1a554673e9c1d7667deece1e5088ab5b9b5..12633e79b14a66762b37cd3f3f7558826bf1d614 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,20 @@
+2009-04-09  Nicolas Setton  <setton@adacore.com>
+
+	* s-osinte-darwin.ads: Fix wrong binding to struc timeval.
+
+	* s-osinte-darwin.adb (To_Timeval): Adapt to fixed implementation of
+	struct_timeval.
+
+2009-04-09  Bob Duff  <duff@adacore.com>
+
+	* exp_ch5.adb, exp_ch9.adb: Correct miscellaneous Slocs in
+	internally-generated nodes related to select statements to avoid
+	confusing the debugger.
+
+2009-04-09  Pascal Obry  <obry@adacore.com>
+
+	* make.adb: Ensure that all linker arguments are duplicated.
+
 2009-04-09  Robert Dewar  <dewar@adacore.com>
 
 	* sem_ch5.adb: Minor reformatting
diff --git a/gcc/ada/exp_ch5.adb b/gcc/ada/exp_ch5.adb
index b20d5685ac15e4238934be755815a22564687ae9..83f20774cb0ea9ba9f093dfc521ff5d08ff6fe13 100644
--- a/gcc/ada/exp_ch5.adb
+++ b/gcc/ada/exp_ch5.adb
@@ -3631,7 +3631,7 @@ package body Exp_Ch5 is
          Call :=
            Make_Procedure_Call_Statement (Loc,
              Name => New_Reference_To
-                       (RTE (RE_Complete_Rendezvous), Loc));
+                       (RTE (RE_Complete_Rendezvous), No_Location));
          Insert_Before (N, Call);
          --  why not insert actions here???
          Analyze (Call);
diff --git a/gcc/ada/exp_ch9.adb b/gcc/ada/exp_ch9.adb
index b0e81eb6490f71e08da96126ab93ae5d7056ff58..bff65b361d6fe082c6ba168ee9575e1979c63cee 100644
--- a/gcc/ada/exp_ch9.adb
+++ b/gcc/ada/exp_ch9.adb
@@ -740,7 +740,7 @@ package body Exp_Ch9 is
       --  processing, has already been added for the expansion of requeue
       --  statements.
 
-      Call := Build_Runtime_Call (Loc, RE_Complete_Rendezvous);
+      Call := Build_Runtime_Call (No_Location, RE_Complete_Rendezvous);
       Insert_Before (Last (Statements (Stats)), Call);
       Analyze (Call);
 
@@ -751,7 +751,7 @@ package body Exp_Ch9 is
          Hand := First (Exception_Handlers (Stats));
 
          while Present (Hand) loop
-            Call := Build_Runtime_Call (Loc, RE_Complete_Rendezvous);
+            Call := Build_Runtime_Call (No_Location, RE_Complete_Rendezvous);
             Append (Call, Statements (Hand));
             Analyze (Call);
             Next (Hand);
@@ -786,13 +786,13 @@ package body Exp_Ch9 is
             Exception_Choices => New_List (Ohandle),
 
             Statements =>  New_List (
-              Make_Procedure_Call_Statement (Loc,
+              Make_Procedure_Call_Statement (No_Location,
                 Name => New_Reference_To (
-                  RTE (RE_Exceptional_Complete_Rendezvous), Loc),
+                  RTE (RE_Exceptional_Complete_Rendezvous), No_Location),
                 Parameter_Associations => New_List (
-                  Make_Function_Call (Loc,
+                  Make_Function_Call (No_Location,
                     Name => New_Reference_To (
-                      RTE (RE_Get_GNAT_Exception), Loc))))))));
+                      RTE (RE_Get_GNAT_Exception), No_Location))))))));
 
       Set_Parent (New_S, Astat); -- temp parent for Analyze call
       Analyze_Exception_Handlers (Exception_Handlers (New_S));
@@ -4663,14 +4663,14 @@ package body Exp_Ch9 is
                while Present (Formal) loop
                   Comp  := Entry_Component (Formal);
                   New_F :=
-                    Make_Defining_Identifier (Sloc (Formal), Chars (Formal));
+                    Make_Defining_Identifier (Loc, Chars (Formal));
 
                   Set_Etype (New_F, Etype (Formal));
                   Set_Scope (New_F, Ent);
 
-               --  Now we set debug info needed on New_F even though it does
-               --  not come from source, so that the debugger will get the
-               --  right information for these generated names.
+                  --  Now we set debug info needed on New_F even though it does
+                  --  not come from source, so that the debugger will get the
+                  --  right information for these generated names.
 
                   Set_Debug_Info_Needed (New_F);
 
@@ -8561,6 +8561,7 @@ package body Exp_Ch9 is
       procedure Add_Accept (Alt : Node_Id) is
          Acc_Stm   : constant Node_Id    := Accept_Statement (Alt);
          Ename     : constant Node_Id    := Entry_Direct_Name (Acc_Stm);
+         Eloc      : constant Source_Ptr := Sloc (Ename);
          Eent      : constant Entity_Id  := Entity (Ename);
          Index     : constant Node_Id    := Entry_Index (Acc_Stm);
          Null_Body : Node_Id;
@@ -8576,29 +8577,29 @@ package body Exp_Ch9 is
 
          if Present (Condition (Alt)) then
             Expr :=
-              Make_Conditional_Expression (Loc, New_List (
+              Make_Conditional_Expression (Eloc, New_List (
                 Condition (Alt),
-                Entry_Index_Expression (Loc, Eent, Index, Scope (Eent)),
-                New_Reference_To (RTE (RE_Null_Task_Entry), Loc)));
+                Entry_Index_Expression (Eloc, Eent, Index, Scope (Eent)),
+                New_Reference_To (RTE (RE_Null_Task_Entry), Eloc)));
          else
             Expr :=
               Entry_Index_Expression
-                (Loc, Eent, Index, Scope (Eent));
+                (Eloc, Eent, Index, Scope (Eent));
          end if;
 
          if Present (Handled_Statement_Sequence (Accept_Statement (Alt))) then
-            Null_Body := New_Reference_To (Standard_False, Loc);
+            Null_Body := New_Reference_To (Standard_False, Eloc);
 
             if Abort_Allowed then
-               Call := Make_Procedure_Call_Statement (Loc,
-                 Name => New_Reference_To (RTE (RE_Abort_Undefer), Loc));
+               Call := Make_Procedure_Call_Statement (Eloc,
+                 Name => New_Reference_To (RTE (RE_Abort_Undefer), Eloc));
                Insert_Before (First (Statements (Handled_Statement_Sequence (
                  Accept_Statement (Alt)))), Call);
                Analyze (Call);
             end if;
 
             PB_Ent :=
-              Make_Defining_Identifier (Sloc (Ename),
+              Make_Defining_Identifier (Eloc,
                 New_External_Name (Chars (Ename), 'A', Num_Accept));
 
             if Comes_From_Source (Alt) then
@@ -8606,9 +8607,9 @@ package body Exp_Ch9 is
             end if;
 
             Proc_Body :=
-              Make_Subprogram_Body (Loc,
+              Make_Subprogram_Body (Eloc,
                 Specification =>
-                  Make_Procedure_Specification (Loc,
+                  Make_Procedure_Specification (Eloc,
                     Defining_Unit_Name => PB_Ent),
                Declarations => Declarations (Acc_Stm),
                Handled_Statement_Sequence =>
@@ -8624,7 +8625,7 @@ package body Exp_Ch9 is
             Append (Proc_Body, Body_List);
 
          else
-            Null_Body := New_Reference_To (Standard_True,  Loc);
+            Null_Body := New_Reference_To (Standard_True,  Eloc);
 
             --  if accept statement has declarations, insert above, given that
             --  we are not creating a body for the accept.
@@ -8635,7 +8636,7 @@ package body Exp_Ch9 is
          end if;
 
          Append_To (Accept_List,
-           Make_Aggregate (Loc, Expressions => New_List (Null_Body, Expr)));
+           Make_Aggregate (Eloc, Expressions => New_List (Null_Body, Expr)));
 
          Num_Accept := Num_Accept + 1;
       end Add_Accept;
@@ -8705,9 +8706,9 @@ package body Exp_Ch9 is
               Make_Integer_Literal (Loc, Index));
 
             Alt_Stats := New_List (
-              Make_Procedure_Call_Statement (Loc,
+              Make_Procedure_Call_Statement (Sloc (Proc),
                 Name => New_Reference_To (
-                  Defining_Unit_Name (Specification (Proc)), Loc)));
+                  Defining_Unit_Name (Specification (Proc)), Sloc (Proc))));
          end if;
 
          if Statements (Alt) /= Empty_List then
diff --git a/gcc/ada/make.adb b/gcc/ada/make.adb
index 7a0e1e032ab8abc6770a41169364bc33dcd608f0..57f0cfb50feb5d3019811e47da960eaaae5af0f8 100644
--- a/gcc/ada/make.adb
+++ b/gcc/ada/make.adb
@@ -6453,7 +6453,8 @@ package body Make is
 
                      else
                         Last_Arg := Last_Arg + 1;
-                        Args (Last_Arg) := Linker_Switches.Table (J);
+                        Args (Last_Arg) :=
+                          new String'(Linker_Switches.Table (J).all);
                      end if;
                   end loop;
 
diff --git a/gcc/ada/s-osinte-darwin.adb b/gcc/ada/s-osinte-darwin.adb
index c06228e2ca23bb4087779d597096639ee69355ae..40a125c747f3c88953382f90597a0bc484e6c76b 100644
--- a/gcc/ada/s-osinte-darwin.adb
+++ b/gcc/ada/s-osinte-darwin.adb
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                  B o d y                                 --
 --                                                                          --
---           Copyright (C) 1999-2006 Free Software Foundation, Inc.         --
+--          Copyright (C) 1999-2008, Free Software Foundation, Inc.         --
 --                                                                          --
 -- GNARL 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- --
@@ -95,11 +95,11 @@ package body System.OS_Interface is
    ----------------
 
    function To_Timeval (D : Duration) return struct_timeval is
-      S : int32_t;
+      S : time_t;
       F : Duration;
 
    begin
-      S := int32_t (D);
+      S := time_t (D);
       F := D - Duration (S);
 
       --  If F has negative value due to a round-up, adjust for positive F
diff --git a/gcc/ada/s-osinte-darwin.ads b/gcc/ada/s-osinte-darwin.ads
index 2a3b9282b52a360cd9cd3925f719a6bd6fa17c38..93dfc6b96df2aa51b3c0660debc8e124e52d98cd 100644
--- a/gcc/ada/s-osinte-darwin.ads
+++ b/gcc/ada/s-osinte-darwin.ads
@@ -525,7 +525,7 @@ private
    CLOCK_REALTIME : constant clockid_t := 0;
 
    type struct_timeval is record
-      tv_sec  : int32_t;
+      tv_sec  : time_t;
       tv_usec : int32_t;
    end record;
    pragma Convention (C, struct_timeval);