diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 90db5bfbcc2d4f94823e5e9d0a76e9f1d0e50592..43e94c1346120220c5efc6f91ebcd62aece53943 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,37 @@
+2009-07-29  Douglas B Rupp  <rupp@gnat.com>
+
+	* config/alpha/vms-cc.c: Deleted.
+	* config/alpha/vms-ld.c: Deleted.
+	* config/alpha/t-vms64: Moved to config/vms
+	* config/alpha/vms-crt0-64.c: Moved to config/vms
+	* config/alpha/vms-crt0.c: Moved to config/vms
+	* config/alpha/vms-psxcrt0-64.c: Moved to config/vms
+	* config/alpha/vms-psxcrt0.c: Moved to config/vms
+	* config/alpha/xm-vms.h: Moved to config/vms
+	* config/alpha/x-vms: Moved to config/vms
+	* config/alpha/t-vms (vcrt0.o, pcrt0.o): Move rules to new file
+	config/vms/t-vms.
+	* config/vms/t-vms: Moved here from config/alpha. Alpha specific
+	parts removed. (STMP_FIXPROTO, STMP_FIXINC, LIMITS_H_TEST): Set.
+	(version): Set.
+	* config/vms/t-vms64: Moved here from config/alpha
+	* config/vms/vms-crt0-64.c: Moved here from config/alpha.
+	(argc,argv,envp): Enforce 32bit malloc'ing.
+	* config/vms/vms-psxcrt0-64.c: Likewise.
+	* config/vms/vms-crt0.c: Moved here from config/alpha.
+	* config/vms/vms-psxcrt0.c: Likewise.
+	* config/vms/vms-crtl-64.h: New file.
+	* config/vms/vms-crtl.h: New file.
+	* config/vms/vms.opt: New file.
+	* config/vms/xm-vms64.h: New file.
+	* config/vms/xm-vms.h: Moved here from config/alpha.
+	(STANARD_EXEC_PREFIX, STANDARD_STARTFILE_PREFIX, STANDARD_INCLUDE_DIR):
+	Set.
+	* config/vms/x-vms: Moved here from config/alpha.
+	(version, VMS_EXTRA_PARTS): Moved to t-vms.
+	(vms-ld.o, vms-cc.o): Removed.
+	(LN, LN_S, USE_COLLECT2, POD2MAN): Set.
+
 2009-07-29  Douglas B Rupp  <rupp@gnat.com>
 
 	* dwarf2out.c (add_name_and_src_coords_attributes): Push on the
diff --git a/gcc/config/alpha/t-vms b/gcc/config/alpha/t-vms
index 5b815288aa3186beb3976515f18d3a0ef411c81b..5e86f14e14bf3c8cac4f8e1a68f515e9c25e028b 100644
--- a/gcc/config/alpha/t-vms
+++ b/gcc/config/alpha/t-vms
@@ -1,5 +1,5 @@
 # Copyright (C) 1996, 1997, 1998, 2001, 2002,
-# 2007 Free Software Foundation, Inc.
+# 2007, 2009 Free Software Foundation, Inc.
 #
 # This file is part of GCC.
 #
@@ -32,13 +32,6 @@ $(T)vms-dwarf2.o : $(srcdir)/config/alpha/vms-dwarf2.asm
 $(T)vms-dwarf2eh.o : $(srcdir)/config/alpha/vms-dwarf2eh.asm
 	gcc -c -x assembler $< -o $@
 
-# Assemble startup files.
-$(T)vcrt0.o: $(CRT0_S) $(GCC_PASSES)
-	decc -c /names=as_is $(srcdir)/config/alpha/vms-crt0.c -o $(T)vcrt0.o
-
-$(T)pcrt0.o: $(CRT0_S) $(GCC_PASSES)
-	decc -c /names=as_is $(srcdir)/config/alpha/vms-psxcrt0.c -o $(T)pcrt0.o
-
 MULTILIB_OPTIONS = mcpu=ev6
 MULTILIB_DIRNAMES = ev6
 LIBGCC = stmp-multilib
diff --git a/gcc/config/alpha/t-vms64 b/gcc/config/alpha/t-vms64
deleted file mode 100644
index 38503a96429052a13e5a881044d8313a010b55d4..0000000000000000000000000000000000000000
--- a/gcc/config/alpha/t-vms64
+++ /dev/null
@@ -1,8 +0,0 @@
-# Assemble startup files.
-$(T)vcrt0.o: $(CRT0_S) $(GCC_PASSES)
-	decc -c /names=as_is /pointer_size=64  \
-	     $(srcdir)/config/alpha/vms-crt0-64.c -o $(T)vcrt0.o
-
-$(T)pcrt0.o: $(CRT0_S) $(GCC_PASSES)
-	decc -c /names=as_is /pointer_size=64 \
-	     $(srcdir)/config/alpha/vms-psxcrt0-64.c -o $(T)pcrt0.o
diff --git a/gcc/config/alpha/vms-cc.c b/gcc/config/alpha/vms-cc.c
deleted file mode 100644
index 9ba2707240f36b24dad92817798040341529d5e1..0000000000000000000000000000000000000000
--- a/gcc/config/alpha/vms-cc.c
+++ /dev/null
@@ -1,355 +0,0 @@
-/* VMS DEC C wrapper.
-   Copyright (C) 2001, 2003, 2007 Free Software Foundation, Inc.
-   Contributed by Douglas B. Rupp (rupp@gnat.com).
-
-This file is part of GCC.
-
-GCC 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 3, or (at your option)
-any later version.
-
-GCC 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 GCC; see the file COPYING3.  If not see
-<http://www.gnu.org/licenses/>.  */
-
-/* This program is a wrapper around the VMS DEC C compiler.
-   It translates Unix style command line options into corresponding
-   VMS style qualifiers and then spawns the DEC C compiler.  */
-
-#include "config.h"
-#include "system.h"
-#include "coretypes.h"
-#include "tm.h"
-
-#undef PATH_SEPARATOR
-#undef PATH_SEPARATOR_STR
-#define PATH_SEPARATOR ','
-#define PATH_SEPARATOR_STR ","
-
-/* These can be set by command line arguments */
-static int verbose = 0;
-static int save_temps = 0;
-
-static int comp_arg_max = -1;
-static const char **comp_args = 0;
-static int comp_arg_index = -1;
-static char *objfilename = 0;
-
-static char *system_search_dirs = (char *) "";
-static char *search_dirs;
-
-static char *default_defines = (char *) "";
-static char *defines;
-
-/* Translate a Unix syntax directory specification into VMS syntax.
-   If indicators of VMS syntax found, return input string.  */
-static char *to_host_dir_spec (char *);
-
-/* Translate a Unix syntax file specification into VMS syntax.
-   If indicators of VMS syntax found, return input string.  */
-static char *to_host_file_spec (char *);
-
-/* Add a translated arg to the list to be passed to DEC CC.  */
-static void addarg (const char *);
-
-/* Preprocess the number of args in P_ARGC and contained in ARGV.
-   Look for special flags, etc. that must be handled first.  */
-static void preprocess_args (int *, char **);
-
-/* Process the number of args in P_ARGC and contained in ARGV. Look
-   for special flags, etc. that must be handled for the VMS compiler.  */
-static void process_args (int *, char **);
-
-/* Action routine called by decc$to_vms */
-static int translate_unix (char *, int);
-
-/* Add the argument contained in STR to the list of arguments to pass to the
-   compiler.  */
-
-static void
-addarg (const char *str)
-{
-  int i;
-
-  if (++comp_arg_index >= comp_arg_max)
-    {
-      const char **new_comp_args
-	= (const char **) xcalloc (comp_arg_max + 1000, sizeof (char *));
-
-      for (i = 0; i <= comp_arg_max; i++)
-	new_comp_args [i] = comp_args [i];
-
-      if (comp_args)
-	free (comp_args);
-
-      comp_arg_max += 1000;
-      comp_args = new_comp_args;
-    }
-
-  comp_args [comp_arg_index] = str;
-}
-
-static void
-preprocess_args (int *p_argc, char *argv[])
-{
-  int i;
-
-  for (i = 1; i < *p_argc; i++)
-    {
-      if (strcmp (argv[i], "-o") == 0)
-	{
-	  char *buff, *ptr;
-
-	  i++;
-	  ptr = to_host_file_spec (argv[i]);
-	  objfilename = xstrdup (ptr);
-	  buff = concat ("/obj=", ptr, NULL);
-	  addarg (buff);
-	}
-    }
-}
-
-static void
-process_args (int *p_argc, char *argv[])
-{
-  int i;
-
-  for (i = 1; i < *p_argc; i++)
-    {
-      if (strlen (argv[i]) < 2)
-	continue;
-
-      if (strncmp (argv[i], "-I", 2) == 0)
-	{
-	  char *ptr;
-	  int new_len, search_dirs_len;
-
-	  ptr = to_host_dir_spec (&argv[i][2]);
-	  new_len = strlen (ptr);
-	  search_dirs_len = strlen (search_dirs);
-
-	  search_dirs = xrealloc (search_dirs, search_dirs_len + new_len + 2);
-	  if (search_dirs_len > 0)
-	    strcat (search_dirs, PATH_SEPARATOR_STR);
-	  strcat (search_dirs, ptr);
-	}
-      else if (strncmp (argv[i], "-D", 2) == 0)
-	{
-	  char *ptr;
-	  int new_len, defines_len;
-
-	  ptr = &argv[i][2];
-	  new_len = strlen (ptr);
-	  defines_len = strlen (defines);
-
-	  defines = xrealloc (defines, defines_len + new_len + 4);
-	  if (defines_len > 0)
-	    strcat (defines, ",");
-
-	  strcat (defines, "\"");
-	  strcat (defines, ptr);
-	  strcat (defines, "\"");
-	}
-      else if (strcmp (argv[i], "-v") == 0)
-	verbose = 1;
-      else if (strcmp (argv[i], "-g0") == 0)
-	addarg ("/nodebug");
-      else if (strcmp (argv[i], "-O0") == 0)
-	addarg ("/noopt");
-      else if (strncmp (argv[i], "-g", 2) == 0)
-	addarg ("/debug");
-      else if (strcmp (argv[i], "-E") == 0)
-	addarg ("/preprocess");
-      else if (strcmp (argv[i], "-save-temps") == 0)
-	save_temps = 1;
-    }
-}
-
-/* The main program.  Spawn the VMS DEC C compiler after fixing up the
-   Unix-like flags and args to be what VMS DEC C wants.  */
-
-typedef struct dsc {unsigned short len, mbz; char *adr; } Descr;
-
-int
-main (int argc, char **argv)
-{
-  int i;
-  char cwdev [128], *devptr;
-  int devlen;
-  char *cwd = getcwd (0, 1024);
-
-  devptr = strchr (cwd, ':');
-  devlen = (devptr - cwd) + 1;
-  strncpy (cwdev, cwd, devlen);
-  cwdev [devlen] = '\0';
-
-  search_dirs = xstrdup (system_search_dirs);
-  defines = xstrdup (default_defines);
-
-  addarg ("cc");
-  preprocess_args (&argc , argv);
-  process_args (&argc , argv);
-
-  if (strlen (search_dirs) > 0)
-    {
-      addarg ("/include=(");
-      addarg (search_dirs);
-      addarg (")");
-    }
-
-  if (strlen (defines) > 0)
-    {
-      addarg ("/define=(");
-      addarg (defines);
-      addarg (")");
-    }
-
-  for (i = 1; i < argc; i++)
-    {
-      int arg_len = strlen (argv[i]);
-
-      if (strcmp (argv[i], "-o") == 0)
-	i++;
-      else if (strcmp (argv[i], "-v" ) == 0
-	       || strcmp (argv[i], "-E") == 0
-	       || strcmp (argv[i], "-c") == 0
-	       || strncmp (argv[i], "-g", 2 ) == 0
-	       || strncmp (argv[i], "-O", 2 ) == 0
-	       || strcmp (argv[i], "-save-temps") == 0
-	       || (arg_len > 2 && strncmp (argv[i], "-I", 2) == 0)
-	       || (arg_len > 2 && strncmp (argv[i], "-D", 2) == 0))
-	;
-
-      /* Unix style file specs and VMS style switches look alike, so assume
-	 an arg consisting of one and only one slash, and that being first, is
-	 really a switch.  */
-      else if ((argv[i][0] == '/') && (strchr (&argv[i][1], '/') == 0))
-	addarg (argv[i]);
-      else
-	{
-	  /* Assume filename arg */
-	  char buff [256], *ptr;
-
-	  ptr = to_host_file_spec (argv[i]);
-	  arg_len = strlen (ptr);
-
-	  if (ptr[0] == '[')
-	    sprintf (buff, "%s%s", cwdev, ptr);
-	  else if (strchr (ptr, ':'))
-	    sprintf (buff, "%s", ptr);
-	  else
-	    sprintf (buff, "%s%s", cwd, ptr);
-
-	  ptr = xstrdup (buff);
-	  addarg (ptr);
-	}
-    }
-
-  addarg (NULL);
-
-  if (verbose)
-    {
-      int i;
-
-      for (i = 0; i < comp_arg_index; i++)
-	printf ("%s ", comp_args [i]);
-
-      putchar ('\n');
-    }
-
-  {
-    int i;
-    int len = 0;
-
-    for (i = 0; comp_args[i]; i++)
-      len = len + strlen (comp_args[i]) + 1;
-
-    {
-      char *allargs = (char *) alloca (len + 1);
-      Descr cmd;
-      int status;
-      int status1 = 1;
-
-      for (i = 0; i < len + 1; i++)
-	allargs [i] = 0;
-
-      for (i = 0; comp_args [i]; i++)
-	{
-	  strcat (allargs, comp_args [i]);
-	  strcat (allargs, " ");
-	}
-
-      cmd.adr = allargs;
-      cmd.len = len;
-      cmd.mbz = 0;
-
-      i = LIB$SPAWN (&cmd, 0, 0, 0, 0, 0, &status);
-
-      if ((i & 1) != 1)
-	{
-	  LIB$SIGNAL (i);
-	  exit (1);
-	}
-
-      if ((status & 1) == 1 && (status1 & 1) == 1)
-	exit (0);
-
-      exit (1);
-    }
-  }
-}
-
-static char new_host_filespec [255];
-static char new_host_dirspec [255];
-static char filename_buff [256];
-
-static int
-translate_unix (char *name, int type ATTRIBUTE_UNUSED)
-{
-  strcpy (filename_buff, name);
-  return 0;
-}
-
-static char *
-to_host_dir_spec (char *dirspec)
-{
-  int len = strlen (dirspec);
-
-  strcpy (new_host_dirspec, dirspec);
-
-  if (strchr (new_host_dirspec, ']') || strchr (new_host_dirspec, ':'))
-    return new_host_dirspec;
-
-  while (len > 1 && new_host_dirspec [len-1] == '/')
-    {
-      new_host_dirspec [len-1] = 0;
-      len--;
-    }
-
-  decc$to_vms (new_host_dirspec, translate_unix, 1, 2);
-  strcpy (new_host_dirspec, filename_buff);
-
-  return new_host_dirspec;
-
-}
-
-static char *
-to_host_file_spec (char *filespec)
-{
-  strcpy (new_host_filespec, "");
-  if (strchr (filespec, ']') || strchr (filespec, ':'))
-    strcpy (new_host_filespec, filespec);
-  else
-    {
-      decc$to_vms (filespec, translate_unix, 1, 1);
-      strcpy (new_host_filespec, filename_buff);
-    }
-
-  return new_host_filespec;
-}
diff --git a/gcc/config/alpha/vms-crt0.c b/gcc/config/alpha/vms-crt0.c
deleted file mode 100644
index affe0e8ac3e526d002e6eef6973ce368588fd148..0000000000000000000000000000000000000000
--- a/gcc/config/alpha/vms-crt0.c
+++ /dev/null
@@ -1,66 +0,0 @@
-/* VMS crt0 returning VMS style condition codes .
-   Copyright (C) 2001, 2009 Free Software Foundation, Inc.
-   Contributed by Douglas B. Rupp (rupp@gnat.com).
-
-This file is part of GCC.
-
-GCC 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 3, or (at your option)
-any later version.
-
-GCC 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.
-
-Under Section 7 of GPL version 3, you are granted additional
-permissions described in the GCC Runtime Library Exception, version
-3.1, as published by the Free Software Foundation.
-
-You should have received a copy of the GNU General Public License and
-a copy of the GCC Runtime Library Exception along with this program;
-see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
-<http://www.gnu.org/licenses/>.  */
-
-#if !defined(__DECC)
-You Lose! This file can only be compiled with DEC C.
-#else
-
-/* This file can only be compiled with DEC C, due to the call to
-   lib$establish.  */
-
-#include <stdlib.h>
-#include <string.h>
-#include <ssdef.h>
-
-extern void decc$main ();
-
-extern int main ();
-
-static int
-handler (sigargs, mechargs)
-     void *sigargs;
-     void *mechargs;
-{
-  return SS$_RESIGNAL;
-}
-
-int
-__main (arg1, arg2, arg3, image_file_desc, arg5, arg6)
-     void *arg1, *arg2, *arg3;
-     void *image_file_desc;
-     void *arg5, *arg6;
-{
-  int argc;
-  char **argv;
-  char **envp;
-
-  lib$establish (handler);
-
-  decc$main(arg1, arg2, arg3, image_file_desc, arg5, arg6,
-	    &argc, &argv, &envp);
-
-  return main (argc, argv, envp);
-}
-#endif
diff --git a/gcc/config/alpha/vms-ld.c b/gcc/config/alpha/vms-ld.c
deleted file mode 100644
index d3b4af27385e26d8791ee9ffa0bb3fe28e67b93f..0000000000000000000000000000000000000000
--- a/gcc/config/alpha/vms-ld.c
+++ /dev/null
@@ -1,763 +0,0 @@
-/* VMS linker wrapper.
-   Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2007
-   Free Software Foundation, Inc.
-   Contributed by Douglas B. Rupp (rupp@gnat.com).
-
-This file is part of GCC.
-
-GCC 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 3, or (at your option)
-any later version.
-
-GCC 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 GCC; see the file COPYING3.  If not see
-<http://www.gnu.org/licenses/>.  */
-
-/* This program is a wrapper around the VMS linker.
-   It translates Unix style command line options into corresponding
-   VMS style qualifiers and then spawns the VMS linker.  */
-
-#include "config.h"
-#include "system.h"
-#include "coretypes.h"
-#include "tm.h"
-
-typedef struct dsc {unsigned short len, mbz; char *adr; } Descr;
-
-#undef PATH_SEPARATOR
-#undef PATH_SEPARATOR_STR
-#define PATH_SEPARATOR ','
-#define PATH_SEPARATOR_STR ","
-
-/* Local variable declarations.  */
-
-/* File specification for vms-dwarf2.o.  */
-static char *vmsdwarf2spec = 0;
-
-/* File specification for vms-dwarf2eh.o.  */
-static char *vmsdwarf2ehspec = 0;
-
-/* verbose = 1 if -v passed.  */
-static int verbose = 0;
-
-/* save_temps = 1 if -save-temps passed.  */
-static int save_temps = 0;
-
-/* By default don't generate executable file if there are errors
-   in the link. Override with --noinhibit-exec.  */
-static int inhibit_exec = 1;
-
-/* debug = 1 if -g passed.  */
-static int debug = 0;
-
-/* By default prefer to link with shareable image libraries.
-   Override with -static.  */
-static int staticp = 0;
-
-/* By default generate an executable, not a shareable image library.
-   Override with -shared.  */
-static int share = 0;
-
-/* Remember if IDENTIFICATION given on command line.  */
-static int ident = 0;
-
-/* Keep track of arg translations.  */
-static int link_arg_max = -1;
-static const char **link_args = 0;
-static int link_arg_index = -1;
-
-/* Keep track of filenames */
-static char optfilefullname [267];
-static char *sharefilename = 0;
-static char *exefilename = 0;
-
-/* System search dir list. Leave blank since link handles this
-   internally.  */
-static char *system_search_dirs = "";
-
-/* Search dir list passed on command line (with -L).  */
-static char *search_dirs;
-
-/* Local function declarations.  */
-
-/* Add STR to the list of arguments to pass to the linker. Expand the list as
-   necessary to accommodate.  */
-static void addarg (const char *);
-
-/* Check to see if NAME is a regular file, i.e. not a directory */
-static int is_regular_file (char *);
-
-/* Translate a Unix syntax file specification FILESPEC into VMS syntax.
-   If indicators of VMS syntax found, return input string.  */
-static char *to_host_file_spec (char *);
-
-/* Locate the library named LIB_NAME in the set of paths PATH_VAL.  */
-static char *locate_lib (char *, char *);
-
-/* Given a library name NAME, i.e. foo,  Look for libfoo.lib and then
-   libfoo.a in the set of directories we are allowed to search in.  */
-static const char *expand_lib (char *);
-
-/* Preprocess the number of args P_ARGC in ARGV.
-   Look for special flags, etc. that must be handled first.  */
-static void preprocess_args (int *, char **);
-
-/* Preprocess the number of args P_ARGC in ARGV.  Look for
-   special flags, etc. that must be handled for the VMS linker.  */
-static void process_args (int *, char **);
-
-/* Action routine called by decc$to_vms. NAME is a file name or
-   directory name. TYPE is unused.  */
-static int translate_unix (char *, int);
-
-int main (int, char **);
-
-static void
-addarg (const char *str)
-{
-  int i;
-
-  if (++link_arg_index >= link_arg_max)
-    {
-      const char **new_link_args
-	= (const char **) xcalloc (link_arg_max + 1000, sizeof (char *));
-
-      for (i = 0; i <= link_arg_max; i++)
-	new_link_args [i] = link_args [i];
-
-      if (link_args)
-	free (link_args);
-
-      link_arg_max += 1000;
-      link_args = new_link_args;
-    }
-
-  link_args [link_arg_index] = str;
-}
-
-static char *
-locate_lib (char *lib_name, char *path_val)
-{
-  int lib_len = strlen (lib_name);
-  char *eptr, *sptr;
-
-  for (sptr = path_val; *sptr; sptr = eptr)
-    {
-      char *buf, *ptr;
-
-      while (*sptr == PATH_SEPARATOR)
-	sptr ++;
-
-      eptr = strchr (sptr, PATH_SEPARATOR);
-      if (eptr == 0)
-	eptr = strchr (sptr, 0);
-
-      buf = alloca ((eptr-sptr) + lib_len + 4 + 2);
-      strncpy (buf, sptr, eptr-sptr);
-      buf [eptr-sptr] = 0;
-      strcat (buf, "/");
-      strcat (buf, lib_name);
-      ptr = strchr (buf, 0);
-
-      if (debug || staticp)
-	{
-	  /* For debug or static links, look for shareable image libraries
-	     last.  */
-	  strcpy (ptr, ".a");
-	  if (is_regular_file (buf))
-	    return xstrdup (to_host_file_spec (buf));
-
-	  strcpy (ptr, ".olb");
-	  if (is_regular_file (buf))
-	    return xstrdup (to_host_file_spec (buf));
-
-	  strcpy (ptr, ".exe");
-	  if (is_regular_file (buf))
-	    return xstrdup (to_host_file_spec (buf));
-	}
-      else
-	{
-	  /* Otherwise look for shareable image libraries first.  */
-	  strcpy (ptr, ".exe");
-	  if (is_regular_file (buf))
-	    return xstrdup (to_host_file_spec (buf));
-
-	  strcpy (ptr, ".a");
-	  if (is_regular_file (buf))
-	    return xstrdup (to_host_file_spec (buf));
-
-	  strcpy (ptr, ".olb");
-	  if (is_regular_file (buf))
-	    return xstrdup (to_host_file_spec (buf));
-	}
-    }
-
-  return 0;
-}
-
-static const char *
-expand_lib (char *name)
-{
-  char *lib, *lib_path;
-
-  if (strcmp (name, "c") == 0)
-    /* IEEE VAX C compatible library for non-prefixed (e.g. no DECC$)
-       C RTL functions.  */
-    return "sys$library:vaxcrtltx.olb";
-
-  else if (strcmp (name, "m") == 0)
-    /* No separate library for math functions */
-    return "";
-
-  else
-    {
-      lib = xmalloc (strlen (name) + 14);
-
-      strcpy (lib, "lib");
-      strcat (lib, name);
-      lib_path = locate_lib (lib, search_dirs);
-
-      if (lib_path)
-	return lib_path;
-    }
-
-  fprintf (stderr,
-	   "Couldn't locate library: lib%s.exe, lib%s.a or lib%s.olb\n",
-	   name, name, name);
-
-  exit (1);
-}
-
-static int
-is_regular_file (char *name)
-{
-  int ret;
-  struct stat statbuf;
-
-  ret = stat (name, &statbuf);
-  return !ret && S_ISREG (statbuf.st_mode);
-}
-
-static void
-preprocess_args (int *p_argc, char **argv)
-{
-  int i;
-
-  for (i = 1; i < *p_argc; i++)
-    if (strlen (argv[i]) >= 6 && strncmp (argv[i], "-shared", 7) == 0)
-      share = 1;
-
-  for (i = 1; i < *p_argc; i++)
-    if (strcmp (argv[i], "-o") == 0)
-      {
-	char *buff, *ptr;
-	int out_len;
-	int len;
-
-	i++;
-	ptr = to_host_file_spec (argv[i]);
-	exefilename = xstrdup (ptr);
-	out_len = strlen (ptr);
-	buff = xmalloc (out_len + 18);
-
-	if (share)
-	  strcpy (buff, "/share=");
-	else
-	  strcpy (buff, "/exe=");
-
-	strcat (buff, ptr);
-	addarg (buff);
-
-	if (share)
-	  {
-	    sharefilename = xmalloc (out_len+5);
-	    if (ptr == strchr (argv[i], ']'))
-	      strcpy (sharefilename, ++ptr);
-	    else if (ptr == strchr (argv[i], ':'))
-	      strcpy (sharefilename, ++ptr);
-	    else if (ptr == strrchr (argv[i], '/'))
-	      strcpy (sharefilename, ++ptr);
-	    else
-	      strcpy (sharefilename, argv[i]);
-
-	    len = strlen (sharefilename);
-	    if (strncasecmp (&sharefilename[len-4], ".exe", 4) == 0)
-	      sharefilename[len-4] = 0;
-
-	    for (ptr = sharefilename; *ptr; ptr++)
-	      *ptr = TOUPPER (*ptr);
-	  }
-      }
-}
-
-static void
-process_args (int *p_argc, char **argv)
-{
-  int i;
-
-  for (i = 1; i < *p_argc; i++)
-    {
-      if (strlen (argv[i]) < 2)
-	continue;
-
-      if (strncmp (argv[i], "-L", 2) == 0)
-	{
-	  char *nbuff, *ptr;
-	  int new_len, search_dirs_len;
-
-	  ptr = &argv[i][2];
-	  new_len = strlen (ptr);
-	  search_dirs_len = strlen (search_dirs);
-
-	  nbuff = xmalloc (new_len + 1);
-	  strcpy (nbuff, ptr);
-
-	  /* Remove trailing slashes.  */
-	  while (new_len > 1 && nbuff [new_len - 1] == '/')
-	    {
-	      nbuff [new_len - 1] = 0;
-	      new_len--;
-	    }
-
-	  search_dirs = xrealloc (search_dirs, search_dirs_len + new_len + 2);
-	  if (search_dirs_len > 0)
-	    strcat (search_dirs, PATH_SEPARATOR_STR);
-
-	  strcat (search_dirs, nbuff);
-	  free (nbuff);
-	}
-
-      /* -v turns on verbose option here and is passed on to gcc.  */
-      else if (strcmp (argv[i], "-v") == 0)
-	verbose = 1;
-      else if (strcmp (argv[i], "-g0") == 0)
-	addarg ("/notraceback");
-      else if (strncmp (argv[i], "-g", 2) == 0)
-	{
-	  addarg ("/debug");
-	  debug = 1;
-	}
-      else if (strcmp (argv[i], "-static") == 0)
-	staticp = 1;
-      else if (strcmp (argv[i], "-map") == 0)
-	{
-	  char *buff, *ptr;
-
-	  buff = xmalloc (strlen (exefilename) + 5);
-	  strcpy (buff, exefilename);
-	  ptr = strchr (buff, '.');
-	  if (ptr)
-	    *ptr = 0;
-
-	  strcat (buff, ".map");
-	  addarg ("/map=");
-	  addarg (buff);
-	  addarg ("/full");
-	}
-      else if (strcmp (argv[i], "-save-temps") == 0)
-	save_temps = 1;
-      else if (strcmp (argv[i], "--noinhibit-exec") == 0)
-	inhibit_exec = 0;
-    }
-}
-
-/* The main program.  Spawn the VMS linker after fixing up the Unix-like flags
-   and args to be what the VMS linker wants.  */
-
-int
-main (int argc, char **argv)
-{
-  int i;
-  char cwdev [128], *devptr;
-  int devlen;
-  int optfd;
-  FILE *optfile;
-  char *cwd = getcwd (0, 1024);
-  char *optfilename;
-
-  devptr = strchr (cwd, ':');
-  devlen = (devptr - cwd) + 1;
-  strncpy (cwdev, cwd, devlen);
-  cwdev [devlen] = '\0';
-
-  search_dirs = xstrdup (system_search_dirs);
-
-  addarg ("link");
-
-  /* Pass to find args that have to be append first.  */
-  preprocess_args (&argc , argv);
-
-  /* Pass to find the rest of the args.  */
-  process_args (&argc , argv);
-
-  /* Create a temp file to hold args, otherwise we can easily exceed the VMS
-     command line length limits.  */
-  optfilename = alloca (strlen ("LDXXXXXX") + 1);
-  strcpy (optfilename, "LDXXXXXX");
-  optfd = mkstemp (optfilename);
-  getcwd (optfilefullname, 256, 1); /* VMS style cwd.  */
-  strcat (optfilefullname, optfilename);
-  strcat (optfilefullname, ".");
-  optfile = fdopen (optfd, "w");
-
-  /* Write out the IDENTIFICATION argument first so that it can be overridden
-     by an options file.  */
-  for (i = 1; i < argc; i++)
-    {
-      int arg_len = strlen (argv[i]);
-
-      if (arg_len > 6 && strncasecmp (argv[i], "IDENT=", 6) == 0)
-	{
-	  /* Comes from command line. If present will always appear before
-	     IDENTIFICATION=... and will override.  */
-
-	  if (!ident)
-	    ident = 1;
-	}
-      else if (arg_len > 15
-	       && strncasecmp (argv[i], "IDENTIFICATION=", 15) == 0)
-	{
-	  /* Comes from pragma Ident ().  */
-
-	  if (!ident)
-	    {
-	      fprintf (optfile, "case_sensitive=yes\n");
-	      fprintf (optfile, "IDENTIFICATION=\"%15.15s\"\n", &argv[i][15]);
-	      fprintf (optfile, "case_sensitive=NO\n");
-	      ident = 1;
-	    }
-	}
-    }
-
-  for (i = 1; i < argc; i++)
-    {
-      int arg_len = strlen (argv[i]);
-
-      if (strcmp (argv[i], "-o") == 0)
-	i++;
-      else if (arg_len > 2 && strncmp (argv[i], "-l", 2) == 0)
-	{
-	  const char *libname = expand_lib (&argv[i][2]);
-	  const char *ext;
-	  int len;
-
-	  if ((len = strlen (libname)) > 0)
-	    {
-	      char buff [256];
-
-	      if (len > 4 && strcasecmp (&libname [len-4], ".exe") == 0)
-		ext = "/shareable";
-	      else
-		ext = "/library";
-
-	      if (libname[0] == '[')
-		sprintf (buff, "%s%s", cwdev, libname);
-	      else
-		sprintf (buff, "%s", libname);
-
-	      fprintf (optfile, "%s%s\n", buff, ext);
-	    }
-	}
-
-      else if (strcmp (argv[i], "-v" ) == 0
-	       || strncmp (argv[i], "-g", 2 ) == 0
-	       || strcmp (argv[i], "-static" ) == 0
-	       || strcmp (argv[i], "-map" ) == 0
-	       || strcmp (argv[i], "-save-temps") == 0
-	       || strcmp (argv[i], "--noinhibit-exec") == 0
-	       || (arg_len > 2 && strncmp (argv[i], "-L", 2) == 0)
-	       || (arg_len >= 6 && strncmp (argv[i], "-share", 6) == 0))
-	;
-      else if (arg_len > 1 && argv[i][0] == '@')
-	{
-	  FILE *atfile;
-	  char *ptr, *ptr1;
-	  struct stat statbuf;
-	  char *buff;
-	  int len;
-
-	  if (stat (&argv[i][1], &statbuf))
-	    {
-	      fprintf (stderr, "Couldn't open linker response file: %s\n",
-		       &argv[i][1]);
-	      exit (1);
-	    }
-
-	  buff = xmalloc (statbuf.st_size + 1);
-	  atfile = fopen (&argv[i][1], "r");
-	  fgets (buff, statbuf.st_size + 1, atfile);
-	  fclose (atfile);
-
-	  len = strlen (buff);
-	  if (buff [len - 1] == '\n')
-	    {
-	      buff [len - 1] = 0;
-	      len--;
-	    }
-
-	  ptr = buff;
-
-	  do
-	  {
-	     ptr1 = strchr (ptr, ' ');
-	     if (ptr1)
-	       *ptr1 = 0;
-	     ptr = to_host_file_spec (ptr);
-	     if (ptr[0] == '[')
-	       fprintf (optfile, "%s%s\n", cwdev, ptr);
-	     else
-	       fprintf (optfile, "%s\n", ptr);
-	     ptr = ptr1 + 1;
-	  } while (ptr1);
-	}
-
-      /* Unix style file specs and VMS style switches look alike, so assume an
-	 arg consisting of one and only one slash, and that being first, is
-	 really a switch.  */
-      else if ((argv[i][0] == '/') && (strchr (&argv[i][1], '/') == 0))
-	addarg (argv[i]);
-      else if (arg_len > 4
-	       && strncasecmp (&argv[i][arg_len-4], ".OPT", 4) == 0)
-	{
-	  FILE *optfile1;
-	  char buff [256];
-
-	  optfile1 = fopen (argv[i], "r");
-	  while (fgets (buff, 256, optfile1))
-	    fputs (buff, optfile);
-
-	  fclose (optfile1);
-	}
-      else if (arg_len > 7 && strncasecmp (argv[i], "GSMATCH", 7) == 0)
-	fprintf (optfile, "%s\n", argv[i]);
-      else if (arg_len > 6 && strncasecmp (argv[i], "IDENT=", 6) == 0)
-	{
-	  /* Comes from command line and will override pragma.  */
-	  fprintf (optfile, "case_sensitive=yes\n");
-	  fprintf (optfile, "IDENT=\"%15.15s\"\n", &argv[i][6]);
-	  fprintf (optfile, "case_sensitive=NO\n");
-	  ident = 1;
-	}
-      else if (arg_len > 15
-	       && strncasecmp (argv[i], "IDENTIFICATION=", 15) == 0)
-	;
-      else
-	{
-	  /* Assume filename arg.  */
-	  const char *addswitch = "";
-	  char buff [256];
-	  int buff_len;
-	  int is_cld = 0;
-
-	  argv[i] = to_host_file_spec (argv[i]);
-	  arg_len = strlen (argv[i]);
-
-	  if (arg_len > 4 && strcasecmp (&argv[i][arg_len-4], ".exe") == 0)
-	    addswitch = "/shareable";
-
-	  if (arg_len > 4 && strcasecmp (&argv[i][arg_len-4], ".cld") == 0)
-	    {
-	      addswitch = "/shareable";
-	      is_cld = 1;
-	    }
-
-	  if (arg_len > 2 && strcasecmp (&argv[i][arg_len-2], ".a") == 0)
-	    addswitch = "/lib";
-
-	  if (arg_len > 4 && strcasecmp (&argv[i][arg_len-4], ".olb") == 0)
-	    addswitch = "/lib";
-
-	  if (argv[i][0] == '[')
-	    sprintf (buff, "%s%s%s\n", cwdev, argv[i], addswitch);
-	  else if (strchr (argv[i], ':'))
-	    sprintf (buff, "%s%s\n", argv[i], addswitch);
-	  else
-	    sprintf (buff, "%s%s%s\n", cwd, argv[i], addswitch);
-
-	  buff_len = strlen (buff);
-
-	  if (buff_len >= 15
-	      && strcasecmp (&buff[buff_len - 15], "vms-dwarf2eh.o\n") == 0)
-	    vmsdwarf2ehspec = xstrdup (buff);
-	  else if (buff_len >= 13
-	      && strcasecmp (&buff[buff_len - 13],"vms-dwarf2.o\n") == 0)
-	    vmsdwarf2spec = xstrdup (buff);
-	  else if (is_cld)
-	    {
-	      addarg (buff);
-	      addarg (",");
-	    }
-	  else
-	    fprintf (optfile, buff);
-	}
-    }
-
-#if 0
-  if (share)
-    fprintf (optfile, "symbol_vector=(main=procedure)\n");
-#endif
-
-  if (vmsdwarf2ehspec)
-    {
-      fprintf (optfile, "case_sensitive=yes\n");
-      fprintf (optfile, "cluster=DWARF2eh,,,%s", vmsdwarf2ehspec);
-      fprintf (optfile, "collect=DWARF2eh,eh_frame\n");
-      fprintf (optfile, "case_sensitive=NO\n");
-    }
-
-  if (debug && vmsdwarf2spec)
-    {
-      fprintf (optfile, "case_sensitive=yes\n");
-      fprintf (optfile, "cluster=DWARF2debug,,,%s", vmsdwarf2spec);
-      fprintf (optfile, "collect=DWARF2debug,debug_abbrev,debug_aranges,-\n");
-      fprintf (optfile, " debug_frame,debug_info,debug_line,debug_loc,-\n");
-      fprintf (optfile, " debug_macinfo,debug_pubnames,debug_str,-\n");
-      fprintf (optfile, " debug_zzzzzz\n");
-      fprintf (optfile, "case_sensitive=NO\n");
-    }
-
-  if (debug && share)
-    {
-      fprintf (optfile, "case_sensitive=yes\n");
-      fprintf (optfile, "symbol_vector=(-\n");
-      fprintf (optfile,
-	       "%s$DWARF2.DEBUG_ABBREV/$dwarf2.debug_abbrev=DATA,-\n",
-	       sharefilename);
-      fprintf (optfile,
-	       "%s$DWARF2.DEBUG_ARANGES/$dwarf2.debug_aranges=DATA,-\n",
-	       sharefilename);
-      fprintf (optfile, "%s$DWARF2.DEBUG_FRAME/$dwarf2.debug_frame=DATA,-\n",
-	       sharefilename);
-      fprintf (optfile, "%s$DWARF2.DEBUG_INFO/$dwarf2.debug_info=DATA,-\n",
-	       sharefilename);
-      fprintf (optfile, "%s$DWARF2.DEBUG_LINE/$dwarf2.debug_line=DATA,-\n",
-	       sharefilename);
-      fprintf (optfile, "%s$DWARF2.DEBUG_LOC/$dwarf2.debug_loc=DATA,-\n",
-	       sharefilename);
-      fprintf (optfile,
-	       "%s$DWARF2.DEBUG_MACINFO/$dwarf2.debug_macinfo=DATA,-\n",
-	       sharefilename);
-      fprintf (optfile,
-	       "%s$DWARF2.DEBUG_PUBNAMES/$dwarf2.debug_pubnames=DATA,-\n",
-	       sharefilename);
-      fprintf (optfile, "%s$DWARF2.DEBUG_STR/$dwarf2.debug_str=DATA,-\n",
-	       sharefilename);
-      fprintf (optfile, "%s$DWARF2.DEBUG_ZZZZZZ/$dwarf2.debug_zzzzzz=DATA)\n",
-	       sharefilename);
-      fprintf (optfile, "case_sensitive=NO\n");
-    }
-
-  fclose (optfile);
-  addarg (optfilefullname);
-  addarg ("/opt");
-
-  addarg (NULL);
-
-  if (verbose)
-    {
-      int i;
-
-      for (i = 0; i < link_arg_index; i++)
-	printf ("%s ", link_args [i]);
-      putchar ('\n');
-    }
-
-  {
-    int i;
-    int len = 0;
-
-    for (i = 0; link_args[i]; i++)
-      len = len + strlen (link_args[i]) + 1;
-
-    {
-      char *allargs = (char *) alloca (len + 1);
-      Descr cmd;
-      int status;
-      int status1 = 1;
-
-      for (i = 0; i < len + 1; i++)
-	allargs [i] = 0;
-
-      for (i = 0; link_args [i]; i++)
-	{
-	  strcat (allargs, link_args [i]);
-	  strcat (allargs, " ");
-	}
-
-      cmd.adr = allargs;
-      cmd.len = len;
-      cmd.mbz = 0;
-
-      i = LIB$SPAWN (&cmd, 0, 0, 0, 0, 0, &status);
-      if ((i & 1) != 1)
-	{
-	  LIB$SIGNAL (i);
-	  exit (1);
-	}
-
-      if (debug && !share)
-	{
-	  strcpy (allargs, "@gnu:[bin]set_exe ");
-	  strcat (allargs, exefilename);
-	  strcat (allargs, " /nodebug /silent");
-	  len = strlen (allargs);
-	  cmd.adr = allargs;
-	  cmd.len = len;
-	  cmd.mbz = 0;
-
-	  if (verbose)
-	    printf (allargs);
-
-	  i = LIB$SPAWN (&cmd, 0, 0, 0, 0, 0, &status1);
-
-	  if ((i & 1) != 1)
-	    {
-	      LIB$SIGNAL (i);
-	      exit (1);
-	    }
-	}
-
-      if (!save_temps)
-	remove (optfilefullname);
-
-      if ((status & 1) == 1 && (status1 & 1) == 1)
-	exit (0);
-
-      if (exefilename && inhibit_exec == 1)
-	remove (exefilename);
-
-      exit (1);
-    }
-  }
-}
-
-static char new_host_filespec [255];
-static char filename_buff [256];
-
-static int
-translate_unix (char *name, int type ATTRIBUTE_UNUSED)
-{
-  strcpy (filename_buff, name);
-  return 0;
-}
-
-static char *
-to_host_file_spec (char *filespec)
-{
-  strcpy (new_host_filespec, "");
-  if (strchr (filespec, ']') || strchr (filespec, ':'))
-    strcpy (new_host_filespec, filespec);
-  else
-    {
-      decc$to_vms (filespec, translate_unix, 1, 1);
-      strcpy (new_host_filespec, filename_buff);
-    }
-
-  return new_host_filespec;
-}
diff --git a/gcc/config/alpha/x-vms b/gcc/config/vms/t-vms
similarity index 51%
rename from gcc/config/alpha/x-vms
rename to gcc/config/vms/t-vms
index 23f960f283cf7c557c3eda4cee6904b00e2d02a9..132a53b205c3d50c973653750e92caac1294e350 100644
--- a/gcc/config/alpha/x-vms
+++ b/gcc/config/vms/t-vms
@@ -1,4 +1,5 @@
-# Copyright (C) 2001, 2002, 2004, 2005, 2008 Free Software Foundation, Inc.
+# Copyright (C) 2009
+# Free Software Foundation, Inc.
 #
 # This file is part of GCC.
 #
@@ -15,24 +16,23 @@
 # You should have received a copy of the GNU General Public License
 # along with GCC; see the file COPYING3.  If not see
 # <http://www.gnu.org/licenses/>.
-#
+
+STMP_FIXPROTO =
+STMP_FIXINC =
+LIMITS_H_TEST = false
+
 # Under VMS, directory names cannot contain dots.
 version:=$(shell echo $(BASEVER_c) | sed -e 's/\./_/g')
 
-libsubdir=$(libdir)/gcc-lib
+# Temporary restriction: VMS_EXTRA_PARTS must be compiled by DEC C.
+#VMS_EXTRA_PARTS=vcrt0.o pcrt0.o
+VMS_EXTRA_PARTS=
 
-# Rules for linker and compiler wrappers.  These are only useful on
-# a VMS host.
-vms-ld.o : $(srcdir)/config/alpha/vms-ld.c
-	$(CC) -c $(ALL_CFLAGS) $(ALL_CPPFLAGS) $(INCLUDES) $< $(OUTPUT_OPTION)
-ld.exe : vms-ld.o
-	$(CC) -o $@ vms-ld.o ../libiberty/libiberty.a
+DECC=`echo $(CC) | sed -e 's/xgcc -B.*/decc$(exeext)/' -e 's/^gcc/decc/' -e 's/^decc/.\/decc/' -e 's/\(.*\)-gcc/\1-decc/'`
 
-vms-cc.o : $(srcdir)/config/alpha/vms-cc.c
-	$(CC) -c $(ALL_CFLAGS) $(ALL_CPPFLAGS) $(INCLUDES) $< $(OUTPUT_OPTION)
-decc.exe : vms-cc.o
-	$(CC) -o $@ vms-cc.o ../libiberty/libiberty.a
+# Assemble startup files.
+$(T)vcrt0.o: $(CRT0_S) $(GCC_PASSES)
+	$(DECC) -c /names=as_is $(srcdir)/config/vms/vms-crt0.c -o $(T)vcrt0.o
 
-# These extra parts can only be compiled on a VMS host and are only needed
-# on a VMS target.  The rules are in t-vms.
-VMS_EXTRA_PARTS=vcrt0.o pcrt0.o
+$(T)pcrt0.o: $(CRT0_S) $(GCC_PASSES)
+	$(DECC) -c /names=as_is $(srcdir)/config/vms/vms-psxcrt0.c -o $(T)pcrt0.o
diff --git a/gcc/config/vms/t-vms64 b/gcc/config/vms/t-vms64
new file mode 100644
index 0000000000000000000000000000000000000000..2fe00692fb59c1f3c1bca31dcf76fc4019962d07
--- /dev/null
+++ b/gcc/config/vms/t-vms64
@@ -0,0 +1,27 @@
+# Copyright (C) 2009
+# Free Software Foundation, Inc.
+#
+# This file is part of GCC.
+#
+# GCC 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 3, or (at your option)
+# any later version.
+#
+# GCC 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 GCC; see the file COPYING3.  If not see
+# <http://www.gnu.org/licenses/>.
+
+# Assemble startup files.
+$(T)vcrt0.o: $(CRT0_S) $(GCC_PASSES)
+	$(DECC) -c /names=as_is /pointer_size=64  \
+	     $(srcdir)/config/vms/vms-crt0-64.c -o $(T)vcrt0.o
+
+$(T)pcrt0.o: $(CRT0_S) $(GCC_PASSES)
+	$(DECC) -c /names=as_is /pointer_size=64 \
+	     $(srcdir)/config/vms/vms-psxcrt0-64.c -o $(T)pcrt0.o
diff --git a/gcc/config/alpha/vms-crt0-64.c b/gcc/config/vms/vms-crt0-64.c
similarity index 50%
rename from gcc/config/alpha/vms-crt0-64.c
rename to gcc/config/vms/vms-crt0-64.c
index 283e8bee964fc3b53f6e3e17b719b41fcac61466..ec59d81d6af619392f83aae82717ac9c49945bf2 100644
--- a/gcc/config/alpha/vms-crt0-64.c
+++ b/gcc/config/vms/vms-crt0-64.c
@@ -2,26 +2,26 @@
    Copyright (C) 2001, 2009 Free Software Foundation, Inc.
    Contributed by Douglas B. Rupp (rupp@gnat.com).
 
-This file is part of GCC.
+   This file is part of GCC.
 
-GCC 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 3, or (at your option)
-any later version.
+   GCC 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 3, or (at your option)
+   any later version.
 
-GCC 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.
+   GCC 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.
 
-Under Section 7 of GPL version 3, you are granted additional
-permissions described in the GCC Runtime Library Exception, version
-3.1, as published by the Free Software Foundation.
+   Under Section 7 of GPL version 3, you are granted additional
+   permissions described in the GCC Runtime Library Exception, version
+   3.1, as published by the Free Software Foundation.
 
-You should have received a copy of the GNU General Public License and
-a copy of the GCC Runtime Library Exception along with this program;
-see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
-<http://www.gnu.org/licenses/>.  */
+   You should have received a copy of the GNU General Public License and
+   a copy of the GCC Runtime Library Exception along with this program;
+   see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
+   <http://www.gnu.org/licenses/>.  */
 
 #if !defined(__DECC)
 You Lose! This file can only be compiled with DEC C.
@@ -72,18 +72,19 @@ __main (arg1, arg2, arg3, image_file_desc, arg5, arg6)
 
 #pragma __pointer_size long
 
-  /* Reallocate argv with 64-bit pointers.  */
-  long_argv = (char **) malloc (sizeof (char *) * (argc + 1));
+  /* Reallocate argv with 64 bit pointers.  */
+  long_argv = (char **) _malloc32 (sizeof (char *) * (argc + 1));
 
   for (i = 0; i < argc; i++)
-    long_argv[i] = strdup (argv[i]);
+    long_argv[i] = (char *) _strdup32 (argv[i]);
 
   long_argv[argc] = (char *) 0;
 
-  long_envp = (char **) malloc (sizeof (char *) * 5);
+  for (i = 0; envp[i]; i++);
+  long_envp = (char **) _malloc32 (sizeof (char *) * (i + 1));
 
   for (i = 0; envp[i]; i++)
-    long_envp[i] = strdup (envp[i]);
+    long_envp[i] = (char *) _strdup32 (envp[i]);
 
   long_envp[i] = (char *) 0;
 
diff --git a/gcc/config/vms/vms-crt0.c b/gcc/config/vms/vms-crt0.c
new file mode 100644
index 0000000000000000000000000000000000000000..c0fdaaf16c6bc5c6cda6cd9264c683e8c9fc2bd5
--- /dev/null
+++ b/gcc/config/vms/vms-crt0.c
@@ -0,0 +1,66 @@
+/* VMS crt0 returning VMS style condition codes .
+   Copyright (C) 2001, 2009 Free Software Foundation, Inc.
+   Contributed by Douglas B. Rupp (rupp@gnat.com).
+
+   This file is part of GCC.
+
+   GCC 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 3, or (at your option)
+   any later version.
+
+   GCC 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.
+
+   Under Section 7 of GPL version 3, you are granted additional
+   permissions described in the GCC Runtime Library Exception, version
+   3.1, as published by the Free Software Foundation.
+
+   You should have received a copy of the GNU General Public License and
+   a copy of the GCC Runtime Library Exception along with this program;
+   see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
+   <http://www.gnu.org/licenses/>.  */
+
+#if !defined(__DECC)
+You Lose! This file can only be compiled with DEC C.
+#else
+
+/* This file can only be compiled with DEC C, due to the call to
+   lib$establish.  */
+
+#include <stdlib.h>
+#include <string.h>
+#include <ssdef.h>
+
+extern void decc$main ();
+
+extern int main ();
+
+static int
+handler (sigargs, mechargs)
+     void *sigargs;
+     void *mechargs;
+{
+  return SS$_RESIGNAL;
+}
+
+int
+__main (arg1, arg2, arg3, image_file_desc, arg5, arg6)
+     void *arg1, *arg2, *arg3;
+     void *image_file_desc;
+     void *arg5, *arg6;
+{
+  int argc;
+  char **argv;
+  char **envp;
+
+  lib$establish (handler);
+
+  decc$main(arg1, arg2, arg3, image_file_desc, arg5, arg6,
+	    &argc, &argv, &envp);
+
+  return main (argc, argv, envp);
+}
+#endif
diff --git a/gcc/config/vms/vms-crtl-64.h b/gcc/config/vms/vms-crtl-64.h
new file mode 100644
index 0000000000000000000000000000000000000000..6b91f31558ab89645c4d940f96dd78fb0c2c38cd
--- /dev/null
+++ b/gcc/config/vms/vms-crtl-64.h
@@ -0,0 +1,190 @@
+/* Definitions of target machine GNU compiler. 64bit VMS version.
+   Copyright (C) 2009 Free Software Foundation, Inc.
+   Contributed by Douglas B Rupp (rupp@gnat.com).
+
+This file is part of GCC.
+
+GCC 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 3, or (at your option)
+any later version.
+
+GCC 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 GCC; see the file COPYING3.  If not see
+<http://www.gnu.org/licenses/>.  */
+
+/* 
+   Correlation array of 64bit standard CRTL names with DECCRTL
+   function names. Currently contains only a partial list,
+   e.g. those functions use in GNAT and GCC. Memory allocation
+   routines are 32bit but this can be overridden by -mmalloc
+   subtarget switch.
+
+   Note: Please keep in alphabetical order.
+*/
+
+#undef CRTL_NAMES
+#define CRTL_NAMES                          \
+{                                           \
+{"_calloc32",    "decc$calloc",       0},   \
+{"_malloc32",    "decc$malloc",       0},   \
+{"_realloc32",   "decc$realloc",      0},   \
+{"_strdup32",    "decc$strdup",       0},   \
+{"abs",          "decc$abs",          0},   \
+{"abort",        "decc$abort",        0},   \
+{"access",       "decc$access",       0},   \
+{"accept",       "decc$accept",       0},   \
+{"acos",         "decc$tacos",        0},   \
+{"alarm",        "decc$alarm",        0},   \
+{"asin",         "decc$tasin",        0},   \
+{"atan",         "decc$tatan",        0},   \
+{"atan2",        "decc$tatan2",       0},   \
+{"atexit",       "decc$atexit",       0},   \
+{"atoi",         "decc$atoi",         0},   \
+{"atoll",        "decc$atoll",        0},   \
+{"atoq",         "decc$atoq",         0},   \
+{"basename",     "decc$_basename64",  0},   \
+{"bcmp",         "decc$bcmp",         0},   \
+{"bcopy",        "decc$bcopy",        0},   \
+{"bsearch",      "decc$_bsearch64",   0},   \
+{"bzero",        "decc$bzero",        0},   \
+{"calloc",       "decc$calloc",       0},   \
+{"ceil",         "decc$tceil",        0},   \
+{"chdir",        "decc$chdir",        0},   \
+{"chown",        "decc$chown",        0},   \
+{"clearerr",     "decc$clearerr",     0},   \
+{"clock",        "decc$clock",        0},   \
+{"close",        "decc$close",        0},   \
+{"cos",          "decc$tcos",         0},   \
+{"connect",      "decc$connect",      0},   \
+{"ctime",        "decc$ctime",        0},   \
+{"dup",          "decc$dup",          0},   \
+{"dup2",         "decc$dup2",         0},   \
+{"exit",         "decc$exit",         0},   \
+{"exp",          "decc$texp",         0},   \
+{"fabs",         "decc$tfabs",        0},   \
+{"fclose",       "decc$fclose",       0},   \
+{"fdopen",       "decc$fdopen",       0},   \
+{"fgetc",        "decc$fgetc",        0},   \
+{"fgets",        "decc$_fgets64",     0},   \
+{"fflush",       "decc$fflush",       0},   \
+{"ffs",          "decc$ffs",          0},   \
+{"floor",        "decc$tfloor",       0},   \
+{"fopen",        "decc$fopen",        0},   \
+{"fputc",        "decc$fputc",        0},   \
+{"fputs",        "decc$fputs",        0},   \
+{"free",         "decc$free",         0},   \
+{"fread",        "decc$fread",        0},   \
+{"freopen",      "decc$freopen",      0},   \
+{"fseek",        "decc$fseek",        0},   \
+{"ftell",        "decc$ftell",        0},   \
+{"fwrite",       "decc$fwrite",       0},   \
+{"getcwd",       "decc$_getcwd64",    0},   \
+{"getegid",      "decc$getegid",      0},   \
+{"getenv",       "decc$getenv",       0},   \
+{"geteuid",      "decc$geteuid",      0},   \
+{"getgid",       "decc$getgid",       0},   \
+{"gethostbyname","decc$gethostbyname",0},   \
+{"getpagesize",  "decc$getpagesize",  0},   \
+{"getpid",       "decc$getpid",       0},   \
+{"getservbyname","decc$getservbyname",0},   \
+{"gettimeofday", "decc$gettimeofday", 0},   \
+{"getuid",       "decc$getuid",       0},   \
+{"htons",        "decc$htons",        0},   \
+{"iconv",        "decc$iconv",        0},   \
+{"index",        "decc$_index64",     0},   \
+{"isatty",       "decc$isatty",       0},   \
+{"isdigit",      "decc$isdigit",      0},   \
+{"kill",         "decc$kill",         0},   \
+{"log",          "decc$tlog",         0},   \
+{"log10",        "decc$tlog10",       0},   \
+{"lseek",        "decc$lseek",        0},   \
+{"ioctl",        "decc$ioctl",        0},   \
+{"malloc",       "decc$malloc",       0},   \
+{"mbstowcs",     "decc$_mbstowcs64",  0},   \
+{"memchr",       "decc$_memchr64",    0},   \
+{"memcmp",       "decc$memcmp",       0},   \
+{"memcpy",       "decc$_memcpy64",    0},   \
+{"memmove",      "decc$_memmove64",   0},   \
+{"memset",       "decc$_memset64",    0},   \
+{"mkstemp",      "decc$mkstemp",      0},   \
+{"mktemp",       "decc$_mktemp64",    0},   \
+{"mmap",         "decc$_mmap64",      0},   \
+{"munmap",       "decc$munmap",       0},   \
+{"nl_langinfo",  "decc$nl_langinfo",  0},   \
+{"pclose",       "decc$pclose",       0},   \
+{"popen",        "decc$popen",        0},   \
+{"pow",          "decc$tpow",         0},   \
+{"printf",       "decc$txprintf",     0},   \
+{"putenv",       "decc$putenv",       0},   \
+{"puts",         "decc$puts",         0},   \
+{"random",       "decc$random",       0},   \
+{"read",         "decc$read",         0},   \
+{"realloc",      "decc$realloc",      0},   \
+{"recv",         "decc$recv",         0},   \
+{"recvfrom",     "decc$recvfrom",     0},   \
+{"rename",       "decc$rename",       0},   \
+{"rewind",       "decc$rewind",       0},   \
+{"rindex",       "decc$_rindex64",    0},   \
+{"rmdir",        "decc$rmdir",        0},   \
+{"send",         "decc$send",         0},   \
+{"sendto",       "decc$sendto",       0},   \
+{"setenv",       "decc$setenv",       0},   \
+{"setlocale",    "decc$setlocale",    0},   \
+{"setvbuf",      "decc$setvbuf",      0},   \
+{"signal",       "decc$signal",       0},   \
+{"sigsetmask",   "decc$sigsetmask",   0},   \
+{"sin",          "decc$tsin",         0},   \
+{"snprintf",     "decc$txsnprintf",   0},   \
+{"socket",       "decc$socket",       0},   \
+{"sqrt",         "decc$tsqrt",        0},   \
+{"strcasecmp",   "decc$strcasecmp",   0},   \
+{"strchr",       "decc$_strchr64",    0},   \
+{"strcpy",       "decc$_strcpy64",    0},   \
+{"strdup",       "decc$strdup",       0},   \
+{"strerror",     "decc$strerror",     0},   \
+{"strlen",       "decc$strlen",       0},   \
+{"strncasecmp",  "decc$strncasecmp",  0},   \
+{"strncmp",      "decc$strncmp",      0},   \
+{"strncpy",      "decc$_strncpy64",   0},   \
+{"strrchr",      "decc$_strrchr64",   0},   \
+{"strstr",       "decc$_strstr64",    0},   \
+{"strtod",       "decc$t_strtod64",   0},   \
+{"strtol",       "decc$_strtoll64",   0},   \
+{"strtoul",      "decc$_strtoull64",  0},   \
+{"sysconf",      "decc$sysconf",      0},   \
+{"system",       "decc$system",       0},   \
+{"tan",          "decc$ttan",         0},   \
+{"time",         "decc$time",         0},   \
+{"times",        "decc$times",        0},   \
+{"tmpfile",      "decc$tmpfile",      0},   \
+{"tmpnam",       "decc$_tmpnam64",    0},   \
+{"ungetc",       "decc$ungetc",       0},   \
+{"unlink",       "decc$unlink",       0},   \
+{"umask",        "decc$umask",        0},   \
+{"utime",        "decc$utime",        0},   \
+{"wait",         "decc$wait",         0},   \
+{"waitpid",      "decc$waitpid",      0},   \
+{"wcswidth",     "decc$wcswidth",     0},   \
+{"write",        "decc$write",        0},   \
+{"vfprintf",     "decc$txvfprintf",   0},   \
+{"vprintf",      "decc$txvprintf",    0},   \
+{"vsprintf",     "decc$txvsprintf",   0},   \
+{"vsnprintf",    "decc$txvsnprintf",  0},   \
+{NULL, NULL, 0}                             \
+}
+
+/* Initialize of libfuncs that are 32/64 bit memory specific.  */
+
+#undef MEM_LIBFUNCS_INIT
+#define MEM_LIBFUNCS_INIT                                 \
+do {                                                      \
+  memcpy_libfunc = init_one_libfunc ("decc$_memcpy64");   \
+  memmove_libfunc = init_one_libfunc ("decc$_memmove64"); \
+  memset_libfunc = init_one_libfunc ("decc$_memset64");   \
+} while (0)
diff --git a/gcc/config/vms/vms-crtl.h b/gcc/config/vms/vms-crtl.h
new file mode 100644
index 0000000000000000000000000000000000000000..39e647ac4368f48dcdeaa34597619b0d31753ef6
--- /dev/null
+++ b/gcc/config/vms/vms-crtl.h
@@ -0,0 +1,186 @@
+/* Definitions of target machine GNU compiler. 32bit VMS version.
+   Copyright (C) 2009 Free Software Foundation, Inc.
+   Contributed by Douglas B Rupp (rupp@gnat.com).
+
+This file is part of GCC.
+
+GCC 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 3, or (at your option)
+any later version.
+
+GCC 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 GCC; see the file COPYING3.  If not see
+<http://www.gnu.org/licenses/>.  */
+
+/* 
+   Correlation array of standard CRTL names with DECCRTL
+   function names. Currently contains only a partial list,
+   e.g. those functions use in GNAT and GCC
+
+   Note: Please keep in alphabetical order.
+*/
+
+#define CRTL_NAMES                          \
+{                                           \
+{"_calloc32",    "decc$calloc",       0},   \
+{"_malloc32",    "decc$malloc",       0},   \
+{"_realloc32",   "decc$realloc",      0},   \
+{"_strdup32",    "decc$strdup",       0},   \
+{"abs",          "decc$abs",          0},   \
+{"abort",        "decc$abort",        0},   \
+{"access",       "decc$access",       0},   \
+{"accept",       "decc$accept",       0},   \
+{"acos",         "decc$tacos",        0},   \
+{"alarm",        "decc$alarm",        0},   \
+{"asin",         "decc$tasin",        0},   \
+{"atan",         "decc$tatan",        0},   \
+{"atan2",        "decc$tatan2",       0},   \
+{"atexit",       "decc$atexit",       0},   \
+{"atoi",         "decc$atoi",         0},   \
+{"atoll",        "decc$atoll",        0},   \
+{"atoq",         "decc$atoq",         0},   \
+{"basename",     "decc$basename",     0},   \
+{"bcmp",         "decc$bcmp",         0},   \
+{"bcopy",        "decc$bcopy",        0},   \
+{"bsearch",      "decc$bsearch",      0},   \
+{"bzero",        "decc$bzero",        0},   \
+{"calloc",       "decc$calloc",       0},   \
+{"ceil",         "decc$tceil",        0},   \
+{"chdir",        "decc$chdir",        0},   \
+{"chown",        "decc$chown",        0},   \
+{"clearerr",     "decc$clearerr",     0},   \
+{"clock",        "decc$clock",        0},   \
+{"close",        "decc$close",        0},   \
+{"cos",          "decc$tcos",         0},   \
+{"connect",      "decc$connect",      0},   \
+{"ctime",        "decc$ctime",        0},   \
+{"dup",          "decc$dup",          0},   \
+{"dup2",         "decc$dup2",         0},   \
+{"exit",         "decc$exit",         0},   \
+{"exp",          "decc$texp",         0},   \
+{"fabs",         "decc$tfabs",        0},   \
+{"fclose",       "decc$fclose",       0},   \
+{"fdopen",       "decc$fdopen",       0},   \
+{"fgetc",        "decc$fgetc",        0},   \
+{"fgets",        "decc$fgets",        0},   \
+{"fflush",       "decc$fflush",       0},   \
+{"ffs",          "decc$ffs",          0},   \
+{"floor",        "decc$tfloor",       0},   \
+{"fopen",        "decc$fopen",        0},   \
+{"fputc",        "decc$fputc",        0},   \
+{"fputs",        "decc$fputs",        0},   \
+{"free",         "decc$free",         0},   \
+{"fread",        "decc$fread",        0},   \
+{"freopen",      "decc$freopen",      0},   \
+{"fseek",        "decc$fseek",        0},   \
+{"ftell",        "decc$ftell",        0},   \
+{"fwrite",       "decc$fwrite",       0},   \
+{"getcwd",       "decc$getcwd",       0},   \
+{"getegid",      "decc$getegid",      0},   \
+{"getenv",       "decc$getenv",       0},   \
+{"geteuid",      "decc$geteuid",      0},   \
+{"getgid",       "decc$getgid",       0},   \
+{"gethostbyname","decc$gethostbyname",0},   \
+{"getpagesize",  "decc$getpagesize",  0},   \
+{"getpid",       "decc$getpid",       0},   \
+{"getservbyname","decc$getservbyname",0},   \
+{"gettimeofday", "decc$gettimeofday", 0},   \
+{"getuid",       "decc$getuid",       0},   \
+{"htons",        "decc$htons",        0},   \
+{"iconv",        "decc$iconv",        0},   \
+{"index",        "decc$index",        0},   \
+{"isatty",       "decc$isatty",       0},   \
+{"isdigit",      "decc$isdigit",      0},   \
+{"kill",         "decc$kill",         0},   \
+{"log",          "decc$tlog",         0},   \
+{"log10",        "decc$tlog10",       0},   \
+{"lseek",        "decc$lseek",        0},   \
+{"ioctl",        "decc$ioctl",        0},   \
+{"malloc",       "decc$malloc",       0},   \
+{"mbstowcs",     "decc$mbstowcs",     0},   \
+{"memchr",       "decc$memchr",       0},   \
+{"memcmp",       "decc$memcmp",       0},   \
+{"memcpy",       "decc$memcpy",       0},   \
+{"memmove",      "decc$memmove",      0},   \
+{"memset",       "decc$memset",       0},   \
+{"mkstemp",      "decc$mkstemp",      0},   \
+{"mktemp",       "decc$mktemp",       0},   \
+{"mmap",         "decc$mmap",         0},   \
+{"munmap",       "decc$munmap",       0},   \
+{"nl_langinfo",  "decc$nl_langinfo",  0},   \
+{"pclose",       "decc$pclose",       0},   \
+{"popen",        "decc$popen",        0},   \
+{"pow",          "decc$tpow",         0},   \
+{"printf",       "decc$txprintf",     0},   \
+{"putenv",       "decc$putenv",       0},   \
+{"puts",         "decc$puts",         0},   \
+{"random",       "decc$random",       0},   \
+{"read",         "decc$read",         0},   \
+{"realloc",      "decc$realloc",      0},   \
+{"recv",         "decc$recv",         0},   \
+{"recvfrom",     "decc$recvfrom",     0},   \
+{"rename",       "decc$rename",       0},   \
+{"rewind",       "decc$rewind",       0},   \
+{"rindex",       "decc$rindex",       0},   \
+{"rmdir",        "decc$rmdir",        0},   \
+{"send",         "decc$send",         0},   \
+{"sendto",       "decc$sendto",       0},   \
+{"setenv",       "decc$setenv",       0},   \
+{"setlocale",    "decc$setlocale",    0},   \
+{"setvbuf",      "decc$setvbuf",      0},   \
+{"signal",       "decc$signal",       0},   \
+{"sigsetmask",   "decc$sigsetmask",   0},   \
+{"sin",          "decc$tsin",         0},   \
+{"snprintf",     "decc$txsnprintf",   0},   \
+{"socket",       "decc$socket",       0},   \
+{"sqrt",         "decc$tsqrt",        0},   \
+{"strcasecmp",   "decc$strcasecmp",   0},   \
+{"strchr",       "decc$strchr",       0},   \
+{"strcpy",       "decc$strcpy",       0},   \
+{"strdup",       "decc$strdup",       0},   \
+{"strerror",     "decc$strerror",     0},   \
+{"strlen",       "decc$strlen",       0},   \
+{"strncasecmp",  "decc$strncasecmp",  0},   \
+{"strncmp",      "decc$strncmp",      0},   \
+{"strncpy",      "decc$strncpy",      0},   \
+{"strrchr",      "decc$strrchr",      0},   \
+{"strstr",       "decc$strstr",       0},   \
+{"strtod",       "decc$tstrtod",      0},   \
+{"strtol",       "decc$strtoll",      0},   \
+{"strtoul",      "decc$strtoull",     0},   \
+{"sysconf",      "decc$sysconf",      0},   \
+{"system",       "decc$system",       0},   \
+{"tan",          "decc$ttan",         0},   \
+{"time",         "decc$time",         0},   \
+{"times",        "decc$times",        0},   \
+{"tmpfile",      "decc$tmpfile",      0},   \
+{"tmpnam",       "decc$tmpnam",       0},   \
+{"ungetc",       "decc$ungetc",       0},   \
+{"unlink",       "decc$unlink",       0},   \
+{"umask",        "decc$umask",        0},   \
+{"utime",        "decc$utime",        0},   \
+{"wait",         "decc$wait",         0},   \
+{"waitpid",      "decc$waitpid",      0},   \
+{"wcswidth",     "decc$wcswidth",     0},   \
+{"write",        "decc$write",        0},   \
+{"vfprintf",     "decc$txvfprintf",   0},   \
+{"vprintf",      "decc$txvprintf",    0},   \
+{"vsprintf",     "decc$txvsprintf",   0},   \
+{"vsnprintf",    "decc$txvsnprintf",  0},   \
+{NULL, NULL, 0}                             \
+}
+
+/* Initialize of libfuncs that are 32/64 bit memory specific.  */
+
+#define MEM_LIBFUNCS_INIT                              \
+do {                                                   \
+  memcpy_libfunc = init_one_libfunc ("decc$memcpy");   \
+  memmove_libfunc = init_one_libfunc ("decc$memmove"); \
+  memset_libfunc = init_one_libfunc ("decc$memset");   \
+} while (0)
diff --git a/gcc/config/alpha/vms-psxcrt0-64.c b/gcc/config/vms/vms-psxcrt0-64.c
similarity index 60%
rename from gcc/config/alpha/vms-psxcrt0-64.c
rename to gcc/config/vms/vms-psxcrt0-64.c
index 1b74b6d18d2600c3fda4f1f361aa2fb7828dc7d2..45afbc9a03d3882e8e3309ff43778dae25e383fa 100644
--- a/gcc/config/alpha/vms-psxcrt0-64.c
+++ b/gcc/config/vms/vms-psxcrt0-64.c
@@ -2,26 +2,26 @@
    Copyright (C) 2001, 2009 Free Software Foundation, Inc.
    Contributed by Douglas B. Rupp (rupp@gnat.com).
 
-This file is part of GCC.
+   This file is part of GCC.
 
-GCC 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 3, or (at your option)
-any later version.
+   GCC 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 3, or (at your option)
+   any later version.
 
-GCC 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.
+   GCC 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.
 
-Under Section 7 of GPL version 3, you are granted additional
-permissions described in the GCC Runtime Library Exception, version
-3.1, as published by the Free Software Foundation.
+   Under Section 7 of GPL version 3, you are granted additional
+   permissions described in the GCC Runtime Library Exception, version
+   3.1, as published by the Free Software Foundation.
 
-You should have received a copy of the GNU General Public License and
-a copy of the GCC Runtime Library Exception along with this program;
-see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
-<http://www.gnu.org/licenses/>.  */
+   You should have received a copy of the GNU General Public License and
+   a copy of the GCC Runtime Library Exception along with this program;
+   see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
+   <http://www.gnu.org/licenses/>.  */
 
 #if !defined(__DECC)
 You Lose! This file can only be compiled with DEC C.
@@ -53,7 +53,7 @@ int
 __main (arg1, arg2, arg3, image_file_desc, arg5, arg6)
      void *arg1, *arg2, *arg3;
      void *image_file_desc;
-     void *arg5, *arg6)
+     void *arg5, *arg6;
 {
   int argc;
   char **argv;
@@ -74,18 +74,19 @@ __main (arg1, arg2, arg3, image_file_desc, arg5, arg6)
 
 #pragma __pointer_size long
 
-  /* Reallocate argv with 64-bit pointers.  */
-  long_argv = (char **) malloc (sizeof (char *) * (argc + 1));
+  /* Reallocate argv with 64 bit pointers.  */
+  long_argv = (char **) _malloc32 (sizeof (char *) * (argc + 1));
 
   for (i = 0; i < argc; i++)
-    long_argv[i] = strdup (argv[i]);
+    long_argv[i] = (char *) _strdup32 (argv[i]);
 
   long_argv[argc] = (char *) 0;
 
-  long_envp = (char **) malloc (sizeof (char *) * 5);
+  for (i = 0; envp[i]; i++);
+  long_envp = (char **) _malloc32 (sizeof (char *) * (i + 1));
 
   for (i = 0; envp[i]; i++)
-    long_envp[i] = strdup (envp[i]);
+    long_envp[i] = (char *) _strdup32 (envp[i]);
 
   long_envp[i] = (char *) 0;
 
diff --git a/gcc/config/alpha/vms-psxcrt0.c b/gcc/config/vms/vms-psxcrt0.c
similarity index 63%
rename from gcc/config/alpha/vms-psxcrt0.c
rename to gcc/config/vms/vms-psxcrt0.c
index 69d97ec75d33d27156e7f933c340fb9928e312af..5ad5ddb0fd832b7b370b3e8bbb84c53378104a8d 100644
--- a/gcc/config/alpha/vms-psxcrt0.c
+++ b/gcc/config/vms/vms-psxcrt0.c
@@ -2,26 +2,26 @@
    Copyright (C) 2001, 2009 Free Software Foundation, Inc.
    Contributed by Douglas B. Rupp (rupp@gnat.com).
 
-This file is part of GCC.
-
-GCC 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 3, or (at your option)
-any later version.
-
-GCC 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.
-
-Under Section 7 of GPL version 3, you are granted additional
-permissions described in the GCC Runtime Library Exception, version
-3.1, as published by the Free Software Foundation.
-
-You should have received a copy of the GNU General Public License and
-a copy of the GCC Runtime Library Exception along with this program;
-see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
-<http://www.gnu.org/licenses/>.  */
+   This file is part of GCC.
+
+   GCC 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 3, or (at your option)
+   any later version.
+
+   GCC 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.
+
+   Under Section 7 of GPL version 3, you are granted additional
+   permissions described in the GCC Runtime Library Exception, version
+   3.1, as published by the Free Software Foundation.
+
+   You should have received a copy of the GNU General Public License and
+   a copy of the GCC Runtime Library Exception along with this program;
+   see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
+   <http://www.gnu.org/licenses/>.  */
 
 #if !defined(__DECC)
 You Lose! This file can only be compiled with DEC C.
diff --git a/gcc/config/vms/vms.opt b/gcc/config/vms/vms.opt
new file mode 100644
index 0000000000000000000000000000000000000000..dd4b46b333e5d0eb1c9424fc20e63fda714ebbfd
--- /dev/null
+++ b/gcc/config/vms/vms.opt
@@ -0,0 +1,25 @@
+; Copyright (C) 2009 Free Software Foundation, Inc.
+;
+; This file is part of GCC.
+;
+; GCC 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 3, or (at your option) any later
+; version.
+;
+; GCC 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 GCC; see the file COPYING3.  If not see
+; <http://www.gnu.org/licenses/>.
+
+mmalloc64
+Target Report Mask(MALLOC64)
+Malloc data into P2 space
+
+mdebug-main=
+Target RejectNegative Joined Var(vms_debug_main)
+Set name of main routine for the debugger
diff --git a/gcc/config/vms/x-vms b/gcc/config/vms/x-vms
new file mode 100644
index 0000000000000000000000000000000000000000..b232c8e6804295ce2d5ac04ab7545c894bfee4dd
--- /dev/null
+++ b/gcc/config/vms/x-vms
@@ -0,0 +1,27 @@
+# Copyright (C) 2001, 2002, 2004, 2005, 2008, 2009
+# Free Software Foundation, Inc.
+#
+# This file is part of GCC.
+#
+# GCC 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 3, or (at your option)
+# any later version.
+#
+# GCC 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 GCC; see the file COPYING3.  If not see
+# <http://www.gnu.org/licenses/>.
+
+LN = cp -p
+LN_S = cp -p
+
+# Doesn't work on VMS
+USE_COLLECT2=
+
+# There are no man pages on VMS
+POD2MAN = false
diff --git a/gcc/config/alpha/xm-vms.h b/gcc/config/vms/xm-vms.h
similarity index 81%
rename from gcc/config/alpha/xm-vms.h
rename to gcc/config/vms/xm-vms.h
index ea95bcfbaed6212c762823b817607d250340052b..7907f9263cfcd0f3fba7d276a00f05d47a116ecf 100644
--- a/gcc/config/alpha/xm-vms.h
+++ b/gcc/config/vms/xm-vms.h
@@ -1,6 +1,7 @@
-/* Configuration for GNU C-compiler for openVMS/Alpha.
-   Copyright (C) 1996, 1997, 2001, 2004, 2007 Free Software Foundation, Inc.
-   Contributed by Klaus Kaempf (kkaempf@progis.de).
+/* Configuration for GCC for hosting on VMS
+   using a Unix style C library.
+   Copyright (C) 1996, 1997, 2001, 2004, 2007, 2009
+   Free Software Foundation, Inc.
 
 This file is part of GCC.
 
@@ -23,17 +24,14 @@ along with GCC; see the file COPYING3.  If not see
 #define VMS
 #endif
 
-/* Define a local equivalent (sort of) for unlink */
-#define unlink remove
-
 /* Causes exit() to be redefined to __posix_exit() and
-   Posix compatible failure and success codes to be used */
+   Posix compatible failure and success codes to be used.  */
 #define _POSIX_EXIT 1
 
-/* Open files in stream mode if not otherwise explicitly specified */
+/* Open files in stream mode if not otherwise explicitly specified.  */
 #define __UNIX_FOPEN 1
 
-/* Write to stdout using fputc to avoid record terminators in pipes */
+/* Write to stdout using fputc to avoid record terminators in pipes.  */
 #define __UNIX_FWRITE 1
 
 #define STDC_HEADERS 1
@@ -54,3 +52,7 @@ do                                                         \
 	  break;                                           \
 	}                                                  \
   } while (0)
+
+#define STANDARD_EXEC_PREFIX "/gnu/libexec/gcc/"
+#define STANDARD_STARTFILE_PREFIX "/gnu/lib/"
+#define STANDARD_INCLUDE_DIR "/gnu/include"
diff --git a/gcc/config/vms/xm-vms64.h b/gcc/config/vms/xm-vms64.h
new file mode 100644
index 0000000000000000000000000000000000000000..9e77f890aaa9aee2de19a3c5a03f3653c137393b
--- /dev/null
+++ b/gcc/config/vms/xm-vms64.h
@@ -0,0 +1,23 @@
+/* Configuration for GCC for hosting on 64bit VMS
+   using a Unix style C library.
+   Copyright (C) 2009
+   Free Software Foundation, Inc.
+
+This file is part of GCC.
+
+GCC 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 3, or (at your option)
+any later version.
+
+GCC 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 GCC; see the file COPYING3.  If not see
+<http://www.gnu.org/licenses/>.  */
+
+#define HOST_LONG_FORMAT "ll"
+#define HOST_PTR_PRINTF "%llp"