diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index cdf71eb59d878576e7e2d397c1a4409874ae0d31..ff0aa85597ec509a28a7ab10e48329e26b83d341 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,19 @@
+Mon Aug 11 14:15:02 1997  Jeffrey A Law  (law@cygnus.com)
+
+	* Integrate tlink patch from jason@cygnus.com
+	* gcc.c (SWITCH_TAKES_ARG): Add 'V', 'B' and 'b'.
+  	(process_command): Increment n_switches for them.  Don't discard
+ 	their args.  Validate them.
+	(main): Escape " marks when creating COLLECT_GCC_OPTIONS.
+	From Rohan Lenard.
+	(process_command): Set include_prefixes from COMPILER_PATH.
+	(main): Set COLLECT_GCC_OPTIONS sooner.
+	* confiugre.in: Link ../ld/ld.new to collect-ld rather than real-ld.
+	* tlink.c, hash.c, hash.h: New files.
+	* Makefile.in (USE_COLLECT2): Always use collect2.
+	(collect2): Depend on and link in hash.o and tlink.o.
+	(tlink.o, hash.o): Add dependencies.
+
 Mon Aug 11 10:04:49 1997  Jeffrey A Law  (law@cygnus.com)
 
 	* Integrate alias analysis changes from jfc@mit.edu
diff --git a/gcc/Makefile.in b/gcc/Makefile.in
index 7d7e6daa684166548115caf345104d11f483df08..76d83967f483795acd784dc983c11986159dbb84 100644
--- a/gcc/Makefile.in
+++ b/gcc/Makefile.in
@@ -313,6 +313,7 @@ USE_COLLECT2 = @will_use_collect2@
 MAYBE_USE_COLLECT2 = @maybe_use_collect2@
 # It is convenient for configure to add the assignment at the beginning,
 # so don't override it here.
+USE_COLLECT2 = ld
 
 # List of extra C and assembler files to add to libgcc1.a.
 # Assembler files should have names ending in `.asm'.
@@ -1169,11 +1170,11 @@ ld: collect2
 	ln collect2$(exeext) ld$(exeext) > /dev/null 2>&1 \
 	   || cp collect2$(exeext) ld$(exeext)
 
-collect2 : collect2.o cplus-dem.o underscore.o version.o \
+collect2: collect2.o tlink.o hash.o cplus-dem.o underscore.o version.o \
 	choose-temp.o $(LIBDEPS)
 # Don't try modifying collect2 (aka ld) in place--it might be linking this.
 	-rm -f collect2$(exeext)
-	$(CC) $(ALL_CFLAGS) $(LDFLAGS) -o $@ collect2.o \
+	$(CC) $(ALL_CFLAGS) $(LDFLAGS) -o $@ collect2.o tlink.o hash.o \
 	  cplus-dem.o underscore.o version.o choose-temp.o $(LIBS)
 
 collect2.o : collect2.c $(CONFIG_H) gstab.h obstack.h demangle.h
@@ -1181,6 +1182,8 @@ collect2.o : collect2.c $(CONFIG_H) gstab.h obstack.h demangle.h
 	-DTARGET_MACHINE=\"$(target_alias)\" $(MAYBE_USE_COLLECT2) \
 	-c `echo $(srcdir)/collect2.c | sed 's,^\./,,'`
 
+tlink.o: tlink.c demangle.h hash.h $(CONFIG_H)
+hash.o: hash.c hash.h
 cplus-dem.o: cplus-dem.c demangle.h
 
 underscore.c: stamp-under ; @true
diff --git a/gcc/collect2.c b/gcc/collect2.c
index e5775192f6c0df6e237d908c8dc58015e053b113..64d98d78db78804bd9de220984ac16e0b464cb1d 100644
--- a/gcc/collect2.c
+++ b/gcc/collect2.c
@@ -1368,17 +1368,20 @@ main (argc, argv)
       fprintf (stderr, "\n");
     }
 
-  /* Load the program, searching all libraries.  */
+  /* Load the program, searching all libraries and attempting to provide
+     undefined symbols from repository information.  */
 
-  collect_execute ("ld", ld1_argv, ldout);
-  do_wait ("ld");
-  dump_file (ldout);
-  unlink (ldout);
+  do_tlink (ld1_argv, object_lst);
 
   /* If -r or they'll be run via some other method, don't build the
      constructor or destructor list, just return now.  */
   if (rflag || ! do_collecting)
-    return 0;
+    {
+      /* But make sure we delete the export file we may have created.  */
+      if (export_file != 0 && export_file[0])
+	maybe_unlink (export_file);
+      return 0;
+    }
 
   /* Examine the namelist with nm and search it for static constructors
      and destructors to call.
diff --git a/gcc/configure b/gcc/configure
index b3181529acc3f745827baad3c8b233cf34c96a11..64999d034abb169ab18dce1d7ed23560ed3d8a95 100755
--- a/gcc/configure
+++ b/gcc/configure
@@ -4219,13 +4219,13 @@ if [ -f ../gas/Makefile ]; then
 fi
 
 # If we have ld in the build tree, make a link to it.
-if [ -f ../ld/Makefile ]; then
-	if [ x$use_collect2 = x ]; then
-		rm -f ld; $symbolic_link ../ld/ld.new ld 2>/dev/null
-	else
-		rm -f collect-ld; $symbolic_link ../ld/ld.new collect-ld 2>/dev/null
-	fi
-fi
+#if [ -f ../ld/Makefile ]; then
+#	if [ x$use_collect2 = x ]; then
+#		rm -f ld; $symbolic_link ../ld/ld.new ld 2>/dev/null
+#	else
+#		rm -f collect-ld; $symbolic_link ../ld/ld.new collect-ld 2>/dev/null
+#	fi
+#fi
 
 # Figure out what language subdirectories are present.
 subdirs=
diff --git a/gcc/configure.in b/gcc/configure.in
index 6656d096245a6ece2d7d7620a733008549490386..da6bdb630ea4f584972c95222968a217345e283f 100644
--- a/gcc/configure.in
+++ b/gcc/configure.in
@@ -2886,11 +2886,11 @@ fi
 
 # If we have ld in the build tree, make a link to it.
 if [[ -f ../ld/Makefile ]]; then
-	if [[ x$use_collect2 = x ]]; then
-		rm -f ld; $symbolic_link ../ld/ld.new ld 2>/dev/null
-	else
+#	if [[ x$use_collect2 = x ]]; then
+#		rm -f ld; $symbolic_link ../ld/ld.new ld 2>/dev/null
+#	else
 		rm -f collect-ld; $symbolic_link ../ld/ld.new collect-ld 2>/dev/null
-	fi
+#	fi
 fi
 
 # Figure out what language subdirectories are present.
diff --git a/gcc/gcc.c b/gcc/gcc.c
index 2027d28c5133e08d1801a3fe258b3f2799839704..4f6237cde636f5eecf13b3e6b847cea11297692a 100644
--- a/gcc/gcc.c
+++ b/gcc/gcc.c
@@ -525,11 +525,12 @@ static struct user_specs *user_specs_head, *user_specs_tail;
 
 /* This defines which switch letters take arguments.  */
 
-#define DEFAULT_SWITCH_TAKES_ARG(CHAR)      \
+#define DEFAULT_SWITCH_TAKES_ARG(CHAR) \
   ((CHAR) == 'D' || (CHAR) == 'U' || (CHAR) == 'o' \
    || (CHAR) == 'e' || (CHAR) == 'T' || (CHAR) == 'u' \
    || (CHAR) == 'I' || (CHAR) == 'm' || (CHAR) == 'x' \
-   || (CHAR) == 'L' || (CHAR) == 'A')
+   || (CHAR) == 'L' || (CHAR) == 'A' || (CHAR) == 'V' \
+   || (CHAR) == 'B' || (CHAR) == 'b')
 
 #ifndef SWITCH_TAKES_ARG
 #define SWITCH_TAKES_ARG(CHAR) DEFAULT_SWITCH_TAKES_ARG(CHAR)
@@ -2391,6 +2392,9 @@ process_command (argc, argv)
 	      else
 		nstore[endp-startp] = 0;
 	      add_prefix (&exec_prefixes, nstore, 0, 0, NULL_PTR);
+	      add_prefix (&include_prefixes,
+			  concat (nstore, "include", NULL_PTR),
+			  0, 0, NULL_PTR);
 	      if (*endp == 0)
 		break;
 	      endp = startp = endp + 1;
@@ -2630,6 +2634,7 @@ process_command (argc, argv)
 	  switch (c)
 	    {
 	    case 'b':
+              n_switches++;
 	      if (p[1] == 0 && i + 1 == argc)
 		fatal ("argument to `-b' is missing");
 	      if (p[1] == 0)
@@ -2681,6 +2686,7 @@ process_command (argc, argv)
 			}
 		    }
 		}
+                n_switches++;
 	      }
 	      break;
 
@@ -2694,6 +2700,7 @@ process_command (argc, argv)
 	      break;
 
 	    case 'V':
+	      n_switches++;
 	      if (p[1] == 0 && i + 1 == argc)
 		fatal ("argument to `-V' is missing");
 	      if (p[1] == 0)
@@ -2884,13 +2891,6 @@ process_command (argc, argv)
 	  register char *p = &argv[i][1];
 	  register int c = *p;
 
-	  if (c == 'B' || c == 'b' || c == 'V')
-	    {
-	      /* Skip a separate arg, if any.  */
-	      if (p[1] == 0)
-		i++;
-	      continue;
-	    }
 	  if (c == 'x')
 	    {
 	      if (p[1] == 0 && i + 1 == argc)
@@ -2952,6 +2952,12 @@ process_command (argc, argv)
 	  /* This is always valid, since gcc.c itself understands it.  */
 	  if (!strcmp (p, "save-temps"))
 	    switches[n_switches].valid = 1;
+          else
+            {
+              char ch = switches[n_switches].part1[0];
+              if (ch == 'V' || ch == 'b' || ch == 'B')
+                switches[n_switches].valid = 1;
+            }
 	  n_switches++;
 	}
       else
@@ -4373,6 +4379,53 @@ main (argc, argv)
 
   process_command (argc, argv);
 
+  {
+    int i;
+    int first_time;
+
+    /* Build COLLECT_GCC_OPTIONS to have all of the options specified to
+       the compiler.  */
+    obstack_grow (&collect_obstack, "COLLECT_GCC_OPTIONS=",
+		  sizeof ("COLLECT_GCC_OPTIONS=")-1);
+
+    first_time = TRUE;
+    for (i = 0; i < n_switches; i++)
+      {
+	char **args;
+	char *p, *q;
+	if (!first_time)
+	  obstack_grow (&collect_obstack, " ", 1);
+
+	first_time = FALSE;
+	obstack_grow (&collect_obstack, "'-", 2);
+        q = switches[i].part1;
+	while (p = (char *) index (q,'\''))
+          {
+            obstack_grow (&collect_obstack, q, p-q);
+            obstack_grow (&collect_obstack, "'\\''", 4);
+            q = ++p;
+          }
+        obstack_grow (&collect_obstack, q, strlen (q));
+	obstack_grow (&collect_obstack, "'", 1);
+
+	for (args = switches[i].args; args && *args; args++)
+	  {
+	    obstack_grow (&collect_obstack, " '", 2);
+	    q = *args;
+	    while (p = (char *) index (q,'\''))
+	      {
+		obstack_grow (&collect_obstack, q, p-q);
+		obstack_grow (&collect_obstack, "'\\''", 4);
+		q = ++p;
+	      }
+	    obstack_grow (&collect_obstack, q, strlen (q));
+	    obstack_grow (&collect_obstack, "'", 1);
+	  }
+      }
+    obstack_grow (&collect_obstack, "\0", 1);
+    putenv (obstack_finish (&collect_obstack));
+  }
+
   /* Initialize the vector of specs to just the default.
      This means one element containing 0s, as a terminator.  */
 
@@ -4676,32 +4729,6 @@ main (argc, argv)
       putenv_from_prefixes (&exec_prefixes, "COMPILER_PATH=");
       putenv_from_prefixes (&startfile_prefixes, "LIBRARY_PATH=");
 
-      /* Build COLLECT_GCC_OPTIONS to have all of the options specified to
-	 the compiler.  */
-      obstack_grow (&collect_obstack, "COLLECT_GCC_OPTIONS=",
-		    sizeof ("COLLECT_GCC_OPTIONS=")-1);
-
-      first_time = TRUE;
-      for (i = 0; i < n_switches; i++)
-	{
-	  char **args;
-	  if (!first_time)
-	    obstack_grow (&collect_obstack, " ", 1);
-
-	  first_time = FALSE;
-	  obstack_grow (&collect_obstack, "-", 1);
-	  obstack_grow (&collect_obstack, switches[i].part1,
-			strlen (switches[i].part1));
-
-	  for (args = switches[i].args; args && *args; args++)
-	    {
-	      obstack_grow (&collect_obstack, " ", 1);
-	      obstack_grow (&collect_obstack, *args, strlen (*args));
-	    }
-	}
-      obstack_grow (&collect_obstack, "\0", 1);
-      putenv (obstack_finish (&collect_obstack));
-
       value = do_spec (link_command_spec);
       if (value < 0)
 	error_count = 1;
diff --git a/gcc/hash.c b/gcc/hash.c
new file mode 100644
index 0000000000000000000000000000000000000000..155ffbf70f800b3bd92478a27ff49be61cabcac8
--- /dev/null
+++ b/gcc/hash.c
@@ -0,0 +1,208 @@
+/* CYGNUS LOCAL: whole file jason */
+/* hash.c -- hash table routines
+   Copyright (C) 1993, 94 Free Software Foundation, Inc.
+   Written by Steve Chamberlain <sac@cygnus.com>
+
+This file was lifted from BFD, the Binary File Descriptor library.
+
+This program 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 2 of the License, or
+(at your option) any later version.
+
+This program 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.
+
+You should have received a copy of the GNU General Public License
+along with this program; if not, write to the Free Software
+Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.  */
+
+#include "config.h"
+#include "hash.h"
+#include "obstack.h"
+
+extern void free PARAMS ((PTR));
+
+/* Obstack allocation and deallocation routines.  */
+#define obstack_chunk_alloc xmalloc
+#define obstack_chunk_free free
+
+extern char * xmalloc ();
+
+/* The default number of entries to use when creating a hash table.  */
+#define DEFAULT_SIZE (1009)
+
+#ifndef NULL
+#define NULL 0
+#endif
+
+/* Create a new hash table, given a number of entries.  */
+
+boolean
+hash_table_init_n (table, newfunc, size)
+     struct hash_table *table;
+     struct hash_entry *(*newfunc) PARAMS ((struct hash_entry *,
+						struct hash_table *,
+						const char *));
+     unsigned int size;
+{
+  unsigned int alloc;
+
+  alloc = size * sizeof (struct hash_entry *);
+  if (!obstack_begin (&table->memory, alloc))
+    {
+      error ("no memory");
+      return false;
+    }
+  table->table = ((struct hash_entry **)
+		  obstack_alloc (&table->memory, alloc));
+  if (!table->table)
+    {
+      error ("no memory");
+      return false;
+    }
+  memset ((PTR) table->table, 0, alloc);
+  table->size = size;
+  table->newfunc = newfunc;
+  return true;
+}
+
+/* Create a new hash table with the default number of entries.  */
+
+boolean
+hash_table_init (table, newfunc)
+     struct hash_table *table;
+     struct hash_entry *(*newfunc) PARAMS ((struct hash_entry *,
+						struct hash_table *,
+						const char *));
+{
+  return hash_table_init_n (table, newfunc, DEFAULT_SIZE);
+}
+
+/* Free a hash table.  */
+
+void
+hash_table_free (table)
+     struct hash_table *table;
+{
+  obstack_free (&table->memory, (PTR) NULL);
+}
+
+/* Look up a string in a hash table.  */
+
+struct hash_entry *
+hash_lookup (table, string, create, copy)
+     struct hash_table *table;
+     const char *string;
+     boolean create;
+     boolean copy;
+{
+  register const unsigned char *s;
+  register unsigned long hash;
+  register unsigned int c;
+  struct hash_entry *hashp;
+  unsigned int len;
+  unsigned int index;
+  
+  hash = 0;
+  len = 0;
+  s = (const unsigned char *) string;
+  while ((c = *s++) != '\0')
+    {
+      hash += c + (c << 17);
+      hash ^= hash >> 2;
+      ++len;
+    }
+  hash += len + (len << 17);
+  hash ^= hash >> 2;
+
+  index = hash % table->size;
+  for (hashp = table->table[index];
+       hashp != (struct hash_entry *) NULL;
+       hashp = hashp->next)
+    {
+      if (hashp->hash == hash
+	  && strcmp (hashp->string, string) == 0)
+	return hashp;
+    }
+
+  if (! create)
+    return (struct hash_entry *) NULL;
+
+  hashp = (*table->newfunc) ((struct hash_entry *) NULL, table, string);
+  if (hashp == (struct hash_entry *) NULL)
+    return (struct hash_entry *) NULL;
+  if (copy)
+    {
+      char *new;
+
+      new = (char *) obstack_alloc (&table->memory, len + 1);
+      if (!new)
+	{
+	  error ("no memory");
+	  return (struct hash_entry *) NULL;
+	}
+      strcpy (new, string);
+      string = new;
+    }
+  hashp->string = string;
+  hashp->hash = hash;
+  hashp->next = table->table[index];
+  table->table[index] = hashp;
+
+  return hashp;
+}
+
+/* Base method for creating a new hash table entry.  */
+
+/*ARGSUSED*/
+struct hash_entry *
+hash_newfunc (entry, table, string)
+     struct hash_entry *entry;
+     struct hash_table *table;
+     const char *string;
+{
+  if (entry == (struct hash_entry *) NULL)
+    entry = ((struct hash_entry *)
+	     hash_allocate (table, sizeof (struct hash_entry)));
+  return entry;
+}
+
+/* Allocate space in a hash table.  */
+
+PTR
+hash_allocate (table, size)
+     struct hash_table *table;
+     unsigned int size;
+{
+  PTR ret;
+
+  ret = obstack_alloc (&table->memory, size);
+  if (ret == NULL && size != 0)
+    error ("no memory");
+  return ret;
+}
+
+/* Traverse a hash table.  */
+
+void
+hash_traverse (table, func, info)
+     struct hash_table *table;
+     boolean (*func) PARAMS ((struct hash_entry *, PTR));
+     PTR info;
+{
+  unsigned int i;
+
+  for (i = 0; i < table->size; i++)
+    {
+      struct hash_entry *p;
+
+      for (p = table->table[i]; p != NULL; p = p->next)
+	{
+	  if (! (*func) (p, info))
+	    return;
+	}
+    }
+}
diff --git a/gcc/hash.h b/gcc/hash.h
new file mode 100644
index 0000000000000000000000000000000000000000..388532abd655435673a43639a97eb0f976b0adc5
--- /dev/null
+++ b/gcc/hash.h
@@ -0,0 +1,131 @@
+/* CYGNUS LOCAL: whole file jason */
+/* Header file for generic hash table support.
+   Copyright (C) 1993, 94 Free Software Foundation, Inc.
+   Written by Steve Chamberlain <sac@cygnus.com>
+
+This file was lifted from BFD, the Binary File Descriptor library.
+
+This program 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 2 of the License, or
+(at your option) any later version.
+
+This program 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.
+
+You should have received a copy of the GNU General Public License
+along with this program; if not, write to the Free Software
+Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.  */
+
+#ifdef IN_GCC
+
+/* Add prototype support.  */
+#ifndef PROTO
+#if defined (USE_PROTOTYPES) ? USE_PROTOTYPES : defined (__STDC__)
+#define PROTO(ARGS) ARGS
+#else
+#define PROTO(ARGS) ()
+#endif
+#endif
+
+#define PARAMS(ARGS) PROTO(ARGS)
+
+#ifdef __STDC__
+#define PTR void *
+#else
+#ifndef const
+#define const
+#endif
+#define PTR char *
+#endif
+
+#else /* ! IN_GCC */
+#include <ansidecl.h>
+#endif /* IN_GCC */
+
+#include "obstack.h"
+
+typedef enum {false, true} boolean;
+
+/* Hash table routines.  There is no way to free up a hash table.  */
+
+/* An element in the hash table.  Most uses will actually use a larger
+   structure, and an instance of this will be the first field.  */
+
+struct hash_entry
+{
+  /* Next entry for this hash code.  */
+  struct hash_entry *next;
+  /* String being hashed.  */
+  const char *string;
+  /* Hash code.  This is the full hash code, not the index into the
+     table.  */
+  unsigned long hash;
+};
+
+/* A hash table.  */
+
+struct hash_table
+{
+  /* The hash array.  */
+  struct hash_entry **table;
+  /* The number of slots in the hash table.  */
+  unsigned int size;
+  /* A function used to create new elements in the hash table.  The
+     first entry is itself a pointer to an element.  When this
+     function is first invoked, this pointer will be NULL.  However,
+     having the pointer permits a hierarchy of method functions to be
+     built each of which calls the function in the superclass.  Thus
+     each function should be written to allocate a new block of memory
+     only if the argument is NULL.  */
+  struct hash_entry *(*newfunc) PARAMS ((struct hash_entry *,
+					 struct hash_table *,
+					 const char *));
+  /* An obstack for this hash table.  */
+  struct obstack memory;
+};
+
+/* Initialize a hash table.  */
+extern boolean hash_table_init
+  PARAMS ((struct hash_table *,
+	   struct hash_entry *(*) (struct hash_entry *,
+				   struct hash_table *,
+				   const char *)));
+
+/* Initialize a hash table specifying a size.  */
+extern boolean hash_table_init_n
+  PARAMS ((struct hash_table *,
+	   struct hash_entry *(*) (struct hash_entry *,
+				   struct hash_table *,
+				   const char *),
+	   unsigned int size));
+
+/* Free up a hash table.  */
+extern void hash_table_free PARAMS ((struct hash_table *));
+
+/* Look up a string in a hash table.  If CREATE is true, a new entry
+   will be created for this string if one does not already exist.  The
+   COPY argument must be true if this routine should copy the string
+   into newly allocated memory when adding an entry.  */
+extern struct hash_entry *hash_lookup
+  PARAMS ((struct hash_table *, const char *, boolean create,
+	   boolean copy));
+
+/* Base method for creating a hash table entry.  */
+extern struct hash_entry *hash_newfunc
+  PARAMS ((struct hash_entry *, struct hash_table *,
+	   const char *));
+
+/* Grab some space for a hash table entry.  */
+extern PTR hash_allocate PARAMS ((struct hash_table *,
+				  unsigned int));
+
+/* Traverse a hash table in a random order, calling a function on each
+   element.  If the function returns false, the traversal stops.  The
+   INFO argument is passed to the function.  */
+extern void hash_traverse PARAMS ((struct hash_table *,
+				   boolean (*) (struct hash_entry *,
+						PTR),
+				   PTR info));
diff --git a/gcc/tlink.c b/gcc/tlink.c
new file mode 100644
index 0000000000000000000000000000000000000000..77b7875c19347e43f525549237497b0096d7b686
--- /dev/null
+++ b/gcc/tlink.c
@@ -0,0 +1,631 @@
+/* CYGNUS LOCAL: whole file jason */
+/* Scan linker error messages for missing template instantiations and provide
+   them.
+
+   Copyright (C) 1995 Free Software Foundation, Inc.
+   Contributed by Jason Merrill (jason@cygnus.com).
+
+This file is part of GNU CC.
+
+GNU CC 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 2, or (at your option)
+any later version.
+
+GNU CC 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.
+
+You should have received a copy of the GNU General Public License
+along with GNU CC; see the file COPYING.  If not, write to
+the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  */
+
+#include <stdio.h>
+#include "config.h"
+#include "hash.h"
+#include "demangle.h"
+
+#define MAX_ITERATIONS 17
+
+/* Obstack allocation and deallocation routines.  */
+#define obstack_chunk_alloc xmalloc
+#define obstack_chunk_free free
+
+extern char * xmalloc PARAMS((unsigned));
+extern void free ();
+extern char * getenv ();
+
+/* Defined in collect2.c.  */
+extern int vflag, debug;
+extern char *ldout;
+extern char *c_file_name;
+extern struct obstack temporary_obstack;
+extern struct obstack permanent_obstack;
+extern char * temporary_firstobj;
+
+/* Defined in the automatically-generated underscore.c.  */
+extern int prepends_underscore;
+
+static int tlink_verbose;
+
+/* Hash table code.  */
+
+typedef struct symbol_hash_entry
+{
+  struct hash_entry root;
+  struct file_hash_entry *file;
+  int chosen;
+  int tweaking;
+  int tweaked;
+} symbol;
+
+typedef struct file_hash_entry
+{
+  struct hash_entry root;
+  const char *args;
+  const char *dir;
+  const char *main;
+  int tweaking;
+} file;
+
+typedef struct demangled_hash_entry
+{
+  struct hash_entry root;
+  const char *mangled;
+} demangled;
+
+static struct hash_table symbol_table;
+
+static struct hash_entry *
+symbol_hash_newfunc (entry, table, string)
+     struct hash_entry *entry;
+     struct hash_table *table;
+     const char *string;
+{
+  struct symbol_hash_entry *ret = (struct symbol_hash_entry *) entry;
+  if (ret == NULL)
+    {
+      ret = ((struct symbol_hash_entry *)
+	     hash_allocate (table, sizeof (struct symbol_hash_entry)));
+      if (ret == NULL)
+	return NULL;
+    }
+  ret = ((struct symbol_hash_entry *)
+     	 hash_newfunc ((struct hash_entry *) ret, table, string));
+  ret->file = NULL;
+  ret->chosen = 0;
+  ret->tweaking = 0;
+  ret->tweaked = 0;
+  return (struct hash_entry *) ret;
+}
+
+static struct symbol_hash_entry *
+symbol_hash_lookup (string, create)
+     const char *string;
+     boolean create;
+{
+  return ((struct symbol_hash_entry *)
+	  hash_lookup (&symbol_table, string, create, true));
+}
+
+static struct hash_table file_table;
+
+static struct hash_entry *
+file_hash_newfunc (entry, table, string)
+     struct hash_entry *entry;
+     struct hash_table *table;
+     const char *string;
+{
+   struct file_hash_entry *ret = (struct file_hash_entry *) entry;
+  if (ret == NULL)
+    {
+      ret = ((struct file_hash_entry *)
+	     hash_allocate (table, sizeof (struct file_hash_entry)));
+      if (ret == NULL)
+	return NULL;
+    }
+  ret = ((struct file_hash_entry *)
+     	 hash_newfunc ((struct hash_entry *) ret, table, string));
+  ret->args = NULL;
+  ret->dir = NULL;
+  ret->main = NULL;
+  ret->tweaking = 0;
+  return (struct hash_entry *) ret;
+}
+
+static struct file_hash_entry *
+file_hash_lookup (string)
+     const char *string;
+{
+  return ((struct file_hash_entry *)
+	  hash_lookup (&file_table, string, true, true));
+}
+
+static struct hash_table demangled_table;
+
+static struct hash_entry *
+demangled_hash_newfunc (entry, table, string)
+     struct hash_entry *entry;
+     struct hash_table *table;
+     const char *string;
+{
+  struct demangled_hash_entry *ret = (struct demangled_hash_entry *) entry;
+  if (ret == NULL)
+    {
+      ret = ((struct demangled_hash_entry *)
+	     hash_allocate (table, sizeof (struct demangled_hash_entry)));
+      if (ret == NULL)
+	return NULL;
+    }
+  ret = ((struct demangled_hash_entry *)
+     	 hash_newfunc ((struct hash_entry *) ret, table, string));
+  ret->mangled = NULL;
+  return (struct hash_entry *) ret;
+}
+
+static struct demangled_hash_entry *
+demangled_hash_lookup (string, create)
+     const char *string;
+     boolean create;
+{
+  return ((struct demangled_hash_entry *)
+	  hash_lookup (&demangled_table, string, create, true));
+}
+
+/* Stack code.  */
+
+struct symbol_stack_entry
+{
+  symbol *value;
+  struct symbol_stack_entry *next;
+};
+struct obstack symbol_stack_obstack;
+struct symbol_stack_entry *symbol_stack;
+
+struct file_stack_entry
+{
+  file *value;
+  struct file_stack_entry *next;
+};
+struct obstack file_stack_obstack;
+struct file_stack_entry *file_stack;
+
+static void
+symbol_push (p)
+     symbol *p;
+{
+  struct symbol_stack_entry *ep = (struct symbol_stack_entry *) obstack_alloc
+    (&symbol_stack_obstack, sizeof (struct symbol_stack_entry));
+  ep->value = p;
+  ep->next = symbol_stack;
+  symbol_stack = ep;
+}
+
+static symbol *
+symbol_pop ()
+{
+  struct symbol_stack_entry *ep = symbol_stack;
+  symbol *p;
+  if (ep == NULL)
+    return NULL;
+  p = ep->value;
+  symbol_stack = ep->next;
+  obstack_free (&symbol_stack_obstack, ep);
+  return p;
+}
+
+static void
+file_push (p)
+     file *p;
+{
+  struct file_stack_entry *ep;
+
+  if (p->tweaking)
+    return;
+
+  ep = (struct file_stack_entry *) obstack_alloc
+    (&file_stack_obstack, sizeof (struct file_stack_entry));
+  ep->value = p;
+  ep->next = file_stack;
+  file_stack = ep;
+  p->tweaking = 1;
+}
+
+static file *
+file_pop ()
+{
+  struct file_stack_entry *ep = file_stack;
+  file *p;
+  if (ep == NULL)
+    return NULL;
+  p = ep->value;
+  file_stack = ep->next;
+  obstack_free (&file_stack_obstack, ep);
+  p->tweaking = 0;
+  return p;
+}
+
+/* Other machinery.  */
+
+static void
+tlink_init ()
+{
+  char *p;
+
+  hash_table_init (&symbol_table, symbol_hash_newfunc);
+  hash_table_init (&file_table, file_hash_newfunc);
+  hash_table_init (&demangled_table, demangled_hash_newfunc);
+  obstack_begin (&symbol_stack_obstack, 0);
+  obstack_begin (&file_stack_obstack, 0);
+
+  p = getenv ("TLINK_VERBOSE");
+  if (p)
+    tlink_verbose = atoi (p);
+  else
+    {
+      tlink_verbose = 1;
+      if (vflag)
+	tlink_verbose = 2;
+      if (debug)
+	tlink_verbose = 3;
+    }
+}
+
+static int
+tlink_execute (prog, argv, redir)
+     char *prog;
+     char **argv;
+     char *redir;
+{
+  collect_execute (prog, argv, redir);
+  return collect_wait (prog);
+} 
+
+static char *
+frob_extension (s, ext)
+     char *s, *ext;
+{
+  char *p = (char *) rindex (s, '/');
+  if (! p)
+    p = s;
+  p = (char *) rindex (p, '.');
+  if (! p)
+    p = s + strlen (s);
+
+  obstack_grow (&temporary_obstack, s, p - s);
+  return obstack_copy0 (&temporary_obstack, ext, strlen (ext));
+}
+
+static char *
+obstack_fgets (stream, ob)
+     FILE *stream;
+     struct obstack *ob;
+{
+  int c;
+  while ((c = getc (stream)) != EOF && c != '\n')
+    obstack_1grow (ob, c);
+  if (obstack_object_size (ob) == 0)
+    return NULL;
+  obstack_1grow (ob, '\0');
+  return obstack_finish (ob);
+}
+
+static char *
+tfgets (stream)
+     FILE *stream;
+{
+  return obstack_fgets (stream, &temporary_obstack);
+}
+
+static char *
+pfgets (stream)
+     FILE *stream;
+{
+  return obstack_fgets (stream, &permanent_obstack);
+}
+
+/* Real tlink code.  */
+
+static void
+freadsym (stream, f, chosen)
+     FILE *stream;
+     file *f;
+     int chosen;
+{
+  symbol *sym;
+
+  {
+    char *name = tfgets (stream);
+    sym = symbol_hash_lookup (name, true);
+  }
+
+  if (sym->file == NULL)
+    {
+      symbol_push (sym);
+      sym->file = f;
+      sym->chosen = chosen;
+    }
+  else if (chosen)
+    {
+      if (sym->chosen && sym->file != f)
+	{
+	  if (sym->chosen == 1)
+	    file_push (sym->file);
+	  else
+	    {
+	      file_push (f);
+	      f = sym->file;
+	      chosen = sym->chosen;
+	    }
+	}
+      sym->file = f;
+      sym->chosen = chosen;
+    }
+}
+
+static void
+read_repo_file (f)
+     file *f;
+{
+  char c;
+  FILE *stream = fopen (f->root.string, "r");
+
+  if (tlink_verbose >= 2)
+    fprintf (stderr, "collect: reading %s\n", f->root.string);
+
+  while (fscanf (stream, "%c ", &c) == 1)
+    {
+      switch (c)
+	{
+	case 'A':
+	  f->args = pfgets (stream);
+	  break;
+	case 'D':
+	  f->dir = pfgets (stream);
+	  break;
+	case 'M':
+	  f->main = pfgets (stream);
+	  break;
+	case 'P':
+	  freadsym (stream, f, 2);
+	  break;
+	case 'C':
+	  freadsym (stream, f, 1);
+	  break;
+	case 'O':
+	  freadsym (stream, f, 0);
+	  break;
+	}
+      obstack_free (&temporary_obstack, temporary_firstobj);
+    }
+  fclose (stream);
+  if (f->args == NULL)
+    f->args = getenv ("COLLECT_GCC_OPTIONS");
+  if (f->dir == NULL)
+    f->dir = ".";
+}
+
+static void
+maybe_tweak (line, f)
+     char *line;
+     file *f;
+{
+  symbol *sym = symbol_hash_lookup (line + 2, false);
+
+  if ((sym->file == f && sym->tweaking)
+      || (sym->file != f && line[0] == 'C'))
+    {
+      sym->tweaking = 0;
+      sym->tweaked = 1;
+
+      if (line[0] == 'O')
+	line[0] = 'C';
+      else
+	line[0] = 'O';
+    }
+}
+
+static int
+recompile_files ()
+{
+  file *f;
+
+  while ((f = file_pop ()) != NULL)
+    {
+      char *line, *command;
+      FILE *stream = fopen (f->root.string, "r");
+      char *outname = frob_extension (f->root.string, ".rnw");
+      FILE *output = fopen (outname, "w");
+
+      while ((line = tfgets (stream)) != NULL)
+	{
+	  switch (line[0])
+	    {
+	    case 'C':
+	    case 'O':
+	      maybe_tweak (line, f);
+	    }
+	  fprintf (output, "%s\n", line);
+	}
+      fclose (stream);
+      fclose (output);
+      rename (outname, f->root.string);
+
+      obstack_grow (&temporary_obstack, "cd ", 3);
+      obstack_grow (&temporary_obstack, f->dir, strlen (f->dir));
+      obstack_grow (&temporary_obstack, "; ", 2);
+      obstack_grow (&temporary_obstack, c_file_name, strlen (c_file_name));
+      obstack_1grow (&temporary_obstack, ' ');
+      obstack_grow (&temporary_obstack, f->args, strlen (f->args));
+      obstack_1grow (&temporary_obstack, ' ');
+      command = obstack_copy0 (&temporary_obstack, f->main, strlen (f->main));
+
+      if (tlink_verbose)
+	fprintf (stderr, "collect: recompiling %s\n", f->main);
+      if (tlink_verbose >= 3)
+	fprintf (stderr, "%s\n", command);
+
+      if (system (command) != 0)
+	return 0;
+
+      read_repo_file (f);
+
+      obstack_free (&temporary_obstack, temporary_firstobj);
+    }
+  return 1;
+}
+
+static int
+read_repo_files (object_lst)
+     char **object_lst;
+{
+  char **object = object_lst;
+
+  for (; *object; object++)
+    {
+      char *p = frob_extension (*object, ".rpo");
+      file *f;
+
+      if (! file_exists (p))
+	continue;
+
+      f = file_hash_lookup (p);
+
+      read_repo_file (f);
+    }
+
+  if (file_stack != NULL && ! recompile_files ())
+    return 0;
+
+  return (symbol_stack != NULL);
+}
+
+static void
+demangle_new_symbols ()
+{
+  symbol *sym;
+
+  while ((sym = symbol_pop ()) != NULL)
+    {
+      demangled *dem;
+      char *p = cplus_demangle (sym->root.string, DMGL_PARAMS | DMGL_ANSI);
+
+      if (! p)
+	continue;
+
+      dem = demangled_hash_lookup (p, true);
+      dem->mangled = sym->root.string;
+    }
+}
+
+static int
+scan_linker_output (fname)
+     char *fname;
+{
+  FILE *stream = fopen (fname, "r");
+  char *line;
+
+  while ((line = tfgets (stream)) != NULL)
+    {
+      char *p = line, *q;
+      symbol *sym;
+      int end;
+      
+      while (*p && isspace (*p))
+	++p;
+
+      if (! *p)
+	continue;
+
+      for (q = p; *q && ! isspace (*q); ++q)
+	;
+
+      /* Try the first word on the line.  */
+      if (*p == '.')
+	++p;
+      if (*p == '_' && prepends_underscore)
+	++p;
+
+      end = ! *q;
+      *q = 0;
+      sym = symbol_hash_lookup (p, false);
+
+      if (! sym && ! end)
+	/* Try a mangled name in `quotes'.  */
+	{
+	  demangled *dem = 0;
+	  p = (char *) index (q+1, '`');
+	  q = 0;
+
+#define MUL "multiple definition of "
+#define UND "undefined reference to "
+
+	  if (p && (p - line > sizeof (MUL)))
+	    {
+	      char *beg = p - sizeof (MUL) + 1;
+	      *p = 0;
+	      if (!strcmp (beg, MUL) || !strcmp (beg, UND))
+		p++, q = (char *) index (p, '\'');
+	    }
+	  if (q)
+	    *q = 0, dem = demangled_hash_lookup (p, false);
+	  if (dem)
+	    sym = symbol_hash_lookup (dem->mangled, false);
+	}
+
+      if (sym && sym->tweaked)
+	return 0;
+      if (sym && !sym->tweaking)
+	{
+	  if (tlink_verbose >= 2)
+	    fprintf (stderr, "collect: tweaking %s in %s\n",
+		     sym->root.string, sym->file->root.string);
+	  sym->tweaking = 1;
+	  file_push (sym->file);
+	}
+	
+      obstack_free (&temporary_obstack, temporary_firstobj);
+    }
+
+  return (file_stack != NULL);
+}
+
+void
+do_tlink (ld_argv, object_lst)
+     char **ld_argv, **object_lst;
+{
+  int exit = tlink_execute ("ld", ld_argv, ldout);
+
+  tlink_init ();
+
+  if (exit)
+    {
+      int i = 0;
+
+      /* Until collect does a better job of figuring out which are object
+	 files, assume that everything on the command line could be.  */
+      if (read_repo_files (ld_argv))
+	while (exit && i++ < MAX_ITERATIONS)
+	  {
+	    if (tlink_verbose >= 3)
+	      dump_file (ldout);
+	    demangle_new_symbols ();
+	    if (! scan_linker_output (ldout))
+	      break;
+	    if (! recompile_files ())
+	      break;
+	    if (tlink_verbose)
+	      fprintf (stderr, "collect: relinking\n");
+	    exit = tlink_execute ("ld", ld_argv, ldout);
+	  }
+    }
+
+  dump_file (ldout);
+  unlink (ldout);
+  if (exit)
+    {
+      error ("ld returned %d exit status", exit);
+      collect_exit (exit);
+    }
+}