diff --git a/MAINTAINERS b/MAINTAINERS
index d44eda43ebd0dd6c6ec20bfa5e6accf3a822b039..9860e31300011c54032ce9f80ce436926061ea9f 100644
--- a/MAINTAINERS
+++ b/MAINTAINERS
@@ -74,6 +74,7 @@ mips port		Richard Sandiford	rdsandiford@googlemail.com
 mmix port		Hans-Peter Nilsson	hp@bitrange.com
 mn10300 port		Jeff Law		law@redhat.com
 mn10300 port		Alexandre Oliva		aoliva@redhat.com
+moxie port		Anthony Green		green@moxielogic.com
 pdp11 port		Paul Koning		ni1d@arrl.net
 picochip port		Hariharan Sandanagobalane	hariharan@picochip.com
 picochip port		Daniel Towner		dant@picochip.com
diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index cb6507a63b543927e975bc3d80dee31df8fc91e5..adc88567464ed9c1ec6aafb6f5958ea5fd5b254d 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,20 @@
+2009-06-10  Anthony Green  <green@moxielogic.com>
+
+	* config/moxie/crti.asm: New file.
+	* config/moxie/crtn.asm: New file.
+	* config/moxie/moxie.c: New file.
+	* config/moxie/moxie.h: New file.
+	* config/moxie/sfp-machine.h: New file.
+	* config/moxie/moxie-protos.h: New file.
+	* config/moxie/t-moxie: Created.
+	* config/moxie/t-moxie-softfp: Created.
+	* config/moxie/moxie.md: Created.
+	* config/moxie/constraints.md: Created.
+	* config.gcc: Add moxie support.
+	* doc/md.texi (Machine Constraints): Add moxie constraints.
+	* doc/contrib.texi (Contributors): Mention moxie port.
+	* doc/install.texi (Specific): Mention the moxie port.
+
 2009-06-09  Ian Lance Taylor  <iant@google.com>
 
 	* system.h (HAVE_DESIGNATED_INITIALIZERS): Don't define if
diff --git a/gcc/config.gcc b/gcc/config.gcc
index 98d4b1ed84343e555dfbb367e3b9ade0dafebcf5..ceb911abf636d17bcd5ac4c1b7398811bf9044c3 100644
--- a/gcc/config.gcc
+++ b/gcc/config.gcc
@@ -274,6 +274,8 @@ crisv32-*)
 	;;
 frv*)	cpu_type=frv
 	;;
+moxie*)	cpu_type=moxie
+	;;
 fido-*-*)
 	cpu_type=m68k
 	extra_headers=math-68881.h
@@ -881,6 +883,13 @@ frv-*-*linux*)
 	         linux.h glibc-stdint.h frv/linux.h frv/frv-abi.h"
 	tmake_file="${tmake_file} frv/t-frv frv/t-linux"
 	;;
+moxie-*-elf)
+	gas=yes
+	gnu_ld=yes
+	tm_file="dbxelf.h elfos.h svr4.h ${tm_file}"
+	extra_parts="crti.o crtn.o crtbegin.o crtend.o"
+	tmake_file="${tmake_file} moxie/t-moxie moxie/t-moxie-softfp soft-fp/t-softfp"
+	;;
 h8300-*-rtems*)
 	tmake_file="h8300/t-h8300 h8300/t-elf t-rtems h8300/t-rtems"
 	tm_file="h8300/h8300.h dbxelf.h elfos.h h8300/elf.h h8300/rtems.h rtems.h newlib-stdint.h"
diff --git a/gcc/config/moxie/constraints.md b/gcc/config/moxie/constraints.md
new file mode 100644
index 0000000000000000000000000000000000000000..038be5d4c6e79464c7fceee92021d9806a4be41d
--- /dev/null
+++ b/gcc/config/moxie/constraints.md
@@ -0,0 +1,52 @@
+;; Constraint definitions for Moxie
+;; Copyright (C) 2009 Free Software Foundation, Inc.
+;; Contributed by Anthony Green <green@moxielogic.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/>.
+
+;; -------------------------------------------------------------------------
+;; Constraints
+;; -------------------------------------------------------------------------
+
+(define_constraint "A"
+  "An absolute address."
+  (and (match_code "mem")
+       (ior (match_test "GET_CODE (XEXP (op, 0)) == SYMBOL_REF")
+	    (match_test "GET_CODE (XEXP (op, 0)) == LABEL_REF")
+	    (match_test "GET_CODE (XEXP (op, 0)) == CONST"))))
+
+(define_constraint "B"
+  "An offset address."
+  (and (match_code "mem")
+       (match_test "GET_CODE (XEXP (op, 0)) == PLUS")))
+
+(define_constraint "W"
+  "A register indirect memory operand."
+  (and (match_code "mem")
+       (match_test "REG_P (XEXP (op, 0))
+		    && REGNO_OK_FOR_BASE_P (REGNO (XEXP (op, 0)))")))
+
+(define_constraint "I"
+  "An 8-bit constant (0..255)"
+  (and (match_code "const_int")
+       (match_test "ival >= 0 && ival <= 255")))
+
+(define_constraint "N"
+  "A constant -(0..255)"
+  (and (match_code "const_int")
+       (match_test "ival >= -255 && ival <= 0")))
+
diff --git a/gcc/config/moxie/crti.asm b/gcc/config/moxie/crti.asm
new file mode 100644
index 0000000000000000000000000000000000000000..f44582799a3421df1e072a00896ae7469f1f2ef1
--- /dev/null
+++ b/gcc/config/moxie/crti.asm
@@ -0,0 +1,40 @@
+# crti.asm for moxie
+#
+#   Copyright (C) 2009 Free Software Foundation
+# 
+# This file 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.
+# 
+# This file 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 just make a stack frame for the contents of the .fini and
+# .init sections.  Users may put any desired instructions in those
+# sections.
+
+	.file		"crti.asm"
+
+	.section	".init"
+	.global	_init
+	.type	_init, @function	
+	.p2align	1
+_init:
+
+	.section	".fini"
+	.global	_fini
+	.type	_fini,@function
+	.p2align	1
+_fini:
diff --git a/gcc/config/moxie/crtn.asm b/gcc/config/moxie/crtn.asm
new file mode 100644
index 0000000000000000000000000000000000000000..3ac9d31eed88514f8d0974e7eb7139f05b002eb3
--- /dev/null
+++ b/gcc/config/moxie/crtn.asm
@@ -0,0 +1,34 @@
+# crtn.asm for moxie
+# 
+#   Copyright (C) 2009 Free Software Foundation
+# 
+# This file 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.
+# 
+# This file 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 just makes sure that the .fini and .init sections do in
+# fact return.  Users may put any desired instructions in those sections.
+# This file is the last thing linked into any executable.
+
+	.file		"crtn.asm"
+
+	.section	".init"
+	ret
+	
+	.section	".fini"
+	ret
diff --git a/gcc/config/moxie/moxie-protos.h b/gcc/config/moxie/moxie-protos.h
new file mode 100644
index 0000000000000000000000000000000000000000..d475aac6a6968ffd2af4a76f8733183e341f3426
--- /dev/null
+++ b/gcc/config/moxie/moxie-protos.h
@@ -0,0 +1,28 @@
+/* Prototypes for moxie.c functions used in the md file & elsewhere.
+   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/>.  */
+
+extern void  moxie_expand_prologue (void);
+extern void  moxie_expand_epilogue (void);
+extern int   moxie_initial_elimination_offset (int, int);
+extern rtx   moxie_function_value (tree, tree, bool ATTRIBUTE_UNUSED);
+extern void  moxie_print_operand (FILE *, rtx, int);
+extern void  moxie_print_operand_address (FILE *, rtx);
+#ifdef RTX_CODE
+extern rtx   moxie_function_arg (CUMULATIVE_ARGS, enum machine_mode, tree, int);
+#endif /* RTX_CODE */
diff --git a/gcc/config/moxie/moxie.c b/gcc/config/moxie/moxie.c
new file mode 100644
index 0000000000000000000000000000000000000000..03e9f3f2485a5fef4bdb0d28d6b2a71a800eece8
--- /dev/null
+++ b/gcc/config/moxie/moxie.c
@@ -0,0 +1,480 @@
+/* Target Code for moxie
+   Copyright (C) 2008, 2009  Free Software Foundation
+   Contributed by Anthony Green.
+
+   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/>.  */
+
+#include "config.h"
+#include "system.h"
+#include "coretypes.h"
+#include "tm.h"
+#include "rtl.h"
+#include "regs.h"
+#include "hard-reg-set.h"
+#include "real.h"
+#include "insn-config.h"
+#include "conditions.h"
+#include "insn-flags.h"
+#include "output.h"
+#include "insn-attr.h"
+#include "flags.h"
+#include "recog.h"
+#include "reload.h"
+#include "toplev.h"
+#include "obstack.h"
+#include "tree.h"
+#include "expr.h"
+#include "optabs.h"
+#include "except.h"
+#include "function.h"
+#include "ggc.h"
+#include "target.h"
+#include "target-def.h"
+#include "tm_p.h"
+#include "langhooks.h"
+#include "df.h"
+
+#define LOSE_AND_RETURN(msgid, x)		\
+  do						\
+    {						\
+      moxie_operand_lossage (msgid, x);		\
+      return;					\
+    } while (0)
+
+/* Worker function for TARGET_RETURN_IN_MEMORY.  */
+
+static bool
+moxie_return_in_memory (const_tree type, const_tree fntype ATTRIBUTE_UNUSED)
+{
+  const HOST_WIDE_INT size = int_size_in_bytes (type);
+  return (size == -1 || size > 2 * UNITS_PER_WORD);
+}
+
+/* Define how to find the value returned by a function.
+   VALTYPE is the data type of the value (as a tree).
+   If the precise function being called is known, FUNC is its
+   FUNCTION_DECL; otherwise, FUNC is 0.  
+
+   We always return values in register $r0 for moxie.  */
+
+rtx
+moxie_function_value (tree valtype, 
+		      tree fntype_or_decl ATTRIBUTE_UNUSED,
+		      bool outgoing ATTRIBUTE_UNUSED)
+{
+  return gen_rtx_REG (TYPE_MODE (valtype), MOXIE_R0);
+}
+
+/* Emit an error message when we're in an asm, and a fatal error for
+   "normal" insns.  Formatted output isn't easily implemented, since we
+   use output_operand_lossage to output the actual message and handle the
+   categorization of the error.  */
+
+static void
+moxie_operand_lossage (const char *msgid, rtx op)
+{
+  debug_rtx (op);
+  output_operand_lossage ("%s", msgid);
+}
+
+/* The PRINT_OPERAND_ADDRESS worker.  */
+
+void
+moxie_print_operand_address (FILE *file, rtx x)
+{
+  switch (GET_CODE (x))
+    {
+    case REG:
+      fprintf (file, "(%s)", reg_names[REGNO (x)]);
+      break;
+      
+    case PLUS:
+      switch (GET_CODE (XEXP (x, 1)))
+	{
+	case CONST_INT:
+	  fprintf (file, "%ld(%s)", 
+		   INTVAL(XEXP (x, 1)), reg_names[REGNO (XEXP (x, 0))]);
+	  break;
+	case SYMBOL_REF:
+	  output_addr_const (file, XEXP (x, 1));
+	  fprintf (file, "(%s)", reg_names[REGNO (XEXP (x, 0))]);
+	  break;
+	case CONST:
+	  {
+	    rtx plus = XEXP (XEXP (x, 1), 0);
+	    if (GET_CODE (XEXP (plus, 0)) == SYMBOL_REF 
+		&& CONST_INT_P (XEXP (plus, 1)))
+	      {
+		output_addr_const(file, XEXP (plus, 0));
+		fprintf (file,"+%ld(%s)", INTVAL (XEXP (plus, 1)),
+			 reg_names[REGNO (XEXP (x, 0))]);
+	      }
+	    else
+	      abort();
+	  }
+	  break;
+	default:
+	  abort();
+	}
+      break;
+
+    default:
+      output_addr_const (file, x);
+      break;
+    }
+}
+
+/* The PRINT_OPERAND worker.  */
+
+void
+moxie_print_operand (FILE *file, rtx x, int code)
+{
+  rtx operand = x;
+
+  /* New code entries should just be added to the switch below.  If
+     handling is finished, just return.  If handling was just a
+     modification of the operand, the modified operand should be put in
+     "operand", and then do a break to let default handling
+     (zero-modifier) output the operand.  */
+
+  switch (code)
+    {
+    case 0:
+      /* No code, print as usual.  */
+      break;
+
+    default:
+      LOSE_AND_RETURN ("invalid operand modifier letter", x);
+    }
+
+  /* Print an operand as without a modifier letter.  */
+  switch (GET_CODE (operand))
+    {
+    case REG:
+      if (REGNO (operand) > MOXIE_R13)
+	internal_error ("internal error: bad register: %d", REGNO (operand));
+      fprintf (file, "%s", reg_names[REGNO (operand)]);
+      return;
+
+    case MEM:
+      output_address (XEXP (operand, 0));
+      return;
+
+    default:
+      /* No need to handle all strange variants, let output_addr_const
+	 do it for us.  */
+      if (CONSTANT_P (operand))
+	{
+	  output_addr_const (file, operand);
+	  return;
+	}
+
+      LOSE_AND_RETURN ("unexpected operand", x);
+    }
+}
+
+/* Per-function machine data.  */
+struct GTY(()) machine_function
+ {
+   /* Number of bytes saved on the stack for callee saved registers.  */
+   int callee_saved_reg_size;
+
+   /* Number of bytes saved on the stack for local variables.  */
+   int local_vars_size;
+
+   /* The sum of 2 sizes: locals vars and padding byte for saving the
+    * registers.  Used in expand_prologue () and expand_epilogue().  */
+   int size_for_adjusting_sp;
+ };
+
+/* Zero initialization is OK for all current fields.  */
+
+static struct machine_function *
+moxie_init_machine_status (void)
+{
+  return GGC_CNEW (struct machine_function);
+}
+
+
+/* The OVERRIDE_OPTIONS worker.
+   All this curently does is set init_machine_status.  */
+void
+moxie_override_options (void)
+{
+  /* Set the per-function-data initializer.  */
+  init_machine_status = moxie_init_machine_status;
+}
+
+/* Compute the size of the local area and the size to be adjusted by the
+ * prologue and epilogue.  */
+
+static void
+moxie_compute_frame (void)
+{
+  /* For aligning the local variables.  */
+  int stack_alignment = STACK_BOUNDARY / BITS_PER_UNIT;
+  int padding_locals;
+  int regno;
+
+  /* Padding needed for each element of the frame.  */
+  cfun->machine->local_vars_size = get_frame_size ();
+
+  /* Align to the stack alignment.  */
+  padding_locals = cfun->machine->local_vars_size % stack_alignment;
+  if (padding_locals)
+    padding_locals = stack_alignment - padding_locals;
+
+  cfun->machine->local_vars_size += padding_locals;
+
+  cfun->machine->callee_saved_reg_size = 0;
+
+  /* Save callee-saved registers.  */
+  for (regno = 0; regno < FIRST_PSEUDO_REGISTER; regno++)
+    if (df_regs_ever_live_p (regno) && (! call_used_regs[regno]))
+      cfun->machine->callee_saved_reg_size += 4;
+
+  cfun->machine->size_for_adjusting_sp = 
+    crtl->args.pretend_args_size
+    + cfun->machine->local_vars_size 
+    + (ACCUMULATE_OUTGOING_ARGS ? crtl->outgoing_args_size : 0);
+}
+
+void
+moxie_expand_prologue (void)
+{
+  int regno;
+  rtx insn;
+
+  moxie_compute_frame ();
+
+  /* Save callee-saved registers.  */
+  for (regno = 0; regno < FIRST_PSEUDO_REGISTER; regno++)
+    {
+      if (!fixed_regs[regno] && df_regs_ever_live_p (regno) && !call_used_regs[regno])
+	{
+	  insn = emit_insn (gen_movsi_push (gen_rtx_REG (Pmode, regno)));
+	  RTX_FRAME_RELATED_P (insn) = 1;
+	}
+    }
+
+  if (cfun->machine->size_for_adjusting_sp > 0)
+    {
+      insn = 
+	emit_insn (gen_movsi (gen_rtx_REG (Pmode, MOXIE_R12), 
+			      GEN_INT (-cfun->machine->size_for_adjusting_sp)));
+      RTX_FRAME_RELATED_P (insn) = 1;
+      insn = emit_insn (gen_addsi3 (stack_pointer_rtx, 
+				    stack_pointer_rtx, 
+				    gen_rtx_REG (Pmode, MOXIE_R12)));
+      RTX_FRAME_RELATED_P (insn) = 1;
+    }
+}
+
+void
+moxie_expand_epilogue (void)
+{
+  int regno;
+  rtx insn, reg, cfa_restores = NULL;
+
+  if (cfun->machine->callee_saved_reg_size != 0)
+    {
+      reg = gen_rtx_REG (Pmode, MOXIE_R12);
+      emit_move_insn (reg,
+		      GEN_INT (-cfun->machine->callee_saved_reg_size));
+      emit_insn (gen_addsi3 (reg, reg, hard_frame_pointer_rtx));
+      insn = emit_move_insn (stack_pointer_rtx, reg);
+      RTX_FRAME_RELATED_P (insn) = 1;
+      add_reg_note (insn, REG_CFA_DEF_CFA,
+		    plus_constant (stack_pointer_rtx,
+				   cfun->machine->callee_saved_reg_size));
+      for (regno = FIRST_PSEUDO_REGISTER; regno-- > 0; )
+	if (!fixed_regs[regno] && !call_used_regs[regno]
+	    && df_regs_ever_live_p (regno))
+	  {
+	    reg = gen_rtx_REG (Pmode, regno);
+	    insn = emit_insn (gen_movsi_pop (reg));
+	    RTX_FRAME_RELATED_P (insn) = 1;
+	    add_reg_note (insn, REG_CFA_ADJUST_CFA,
+			  gen_rtx_SET (VOIDmode, stack_pointer_rtx,
+				       plus_constant (stack_pointer_rtx,
+						      UNITS_PER_WORD)));
+	    add_reg_note (insn, REG_CFA_RESTORE, reg);
+	  }
+    }
+
+  emit_jump_insn (gen_returner ());
+}
+
+/* Implements the macro INITIAL_ELIMINATION_OFFSET, return the OFFSET.  */
+
+int
+moxie_initial_elimination_offset (int from, int to)
+{
+  int ret;
+  
+  if ((from) == FRAME_POINTER_REGNUM && (to) == HARD_FRAME_POINTER_REGNUM)
+    {
+      /* Compute this since we need to use cfun->machine->local_vars_size.  */
+      moxie_compute_frame ();
+      ret = -cfun->machine->callee_saved_reg_size;
+    }
+  else if ((from) == ARG_POINTER_REGNUM && (to) == HARD_FRAME_POINTER_REGNUM)
+    ret = 0x00;
+  else
+    abort ();
+
+  return ret;
+}
+
+/* Worker function for TARGET_SETUP_INCOMING_VARARGS.  */
+
+static void
+moxie_setup_incoming_varargs (CUMULATIVE_ARGS *cum,
+			      enum machine_mode mode ATTRIBUTE_UNUSED,
+			      tree type ATTRIBUTE_UNUSED,
+			      int *pretend_size, int no_rtl)
+{
+  int regno;
+  int regs = 4 - *cum;
+  
+  *pretend_size = regs < 0 ? 0 : GET_MODE_SIZE (SImode) * regs;
+  
+  if (no_rtl)
+    return;
+  
+  for (regno = *cum; regno < 4; regno++)
+    {
+      rtx reg = gen_rtx_REG (SImode, regno);
+      rtx slot = gen_rtx_PLUS (Pmode,
+			       gen_rtx_REG (SImode, ARG_POINTER_REGNUM),
+			       GEN_INT (UNITS_PER_WORD * (3 + (regno-2))));
+      
+      emit_move_insn (gen_rtx_MEM (SImode, slot), reg);
+    }
+}
+
+
+/* Return the fixed registers used for condition codes.  */
+
+static bool
+moxie_fixed_condition_code_regs (unsigned int *p1, unsigned int *p2)
+{
+  *p1 = CC_REG;
+  *p2 = INVALID_REGNUM;
+  return true;
+}
+
+/* Return the next register to be used to hold a function argument or
+   NULL_RTX if there's no more space.  */
+
+rtx
+moxie_function_arg (CUMULATIVE_ARGS cum, enum machine_mode mode,
+		    tree type ATTRIBUTE_UNUSED, int named ATTRIBUTE_UNUSED)
+{
+  if (cum < 4)
+    return gen_rtx_REG (mode, cum);
+  else 
+    return NULL_RTX;
+}
+
+/* Return non-zero if the function argument described by TYPE is to be
+   passed by reference.  */
+
+static bool
+moxie_pass_by_reference (CUMULATIVE_ARGS *cum ATTRIBUTE_UNUSED,
+			 enum machine_mode mode, const_tree type,
+			 bool named ATTRIBUTE_UNUSED)
+{
+  unsigned HOST_WIDE_INT size;
+
+  if (type)
+    {
+      if (AGGREGATE_TYPE_P (type))
+	return true;
+      size = int_size_in_bytes (type);
+    }
+  else
+    size = GET_MODE_SIZE (mode);
+
+  return size > 8;
+}
+
+/* Some function arguments will only partially fit in the registers
+   that hold arguments.  Given a new arg, return the number of bytes
+   that fit in argument passing registers.  */
+
+static int
+moxie_arg_partial_bytes (CUMULATIVE_ARGS *cum,
+			 enum machine_mode mode,
+			 tree type, bool named)
+{
+  int bytes_left, size;
+
+  if (*cum >= 4)
+    return 0;
+
+  if (moxie_pass_by_reference (cum, mode, type, named))
+    size = 4;
+  else if (type)
+    {
+      if (AGGREGATE_TYPE_P (type))
+	return 0;
+      size = int_size_in_bytes (type);
+    }
+  else
+    size = GET_MODE_SIZE (mode);
+
+  bytes_left = 8 - ((*cum - 2) * 4);
+
+  if (size > bytes_left)
+    return bytes_left;
+  else
+    return 0;
+}
+
+/* The Global `targetm' Variable.  */
+
+/* Initialize the GCC target structure.  */
+
+#undef  TARGET_PROMOTE_PROTOTYPES
+#define TARGET_PROMOTE_PROTOTYPES	hook_bool_const_tree_true
+
+#undef  TARGET_RETURN_IN_MEMORY
+#define TARGET_RETURN_IN_MEMORY		moxie_return_in_memory
+#undef  TARGET_MUST_PASS_IN_STACK
+#define TARGET_MUST_PASS_IN_STACK	must_pass_in_stack_var_size
+#undef  TARGET_PASS_BY_REFERENCE
+#define TARGET_PASS_BY_REFERENCE        moxie_pass_by_reference
+#undef  TARGET_ARG_PARTIAL_BYTES
+#define TARGET_ARG_PARTIAL_BYTES        moxie_arg_partial_bytes
+
+
+#undef  TARGET_SETUP_INCOMING_VARARGS
+#define TARGET_SETUP_INCOMING_VARARGS 	moxie_setup_incoming_varargs
+
+#undef	TARGET_FIXED_CONDITION_CODE_REGS
+#define	TARGET_FIXED_CONDITION_CODE_REGS moxie_fixed_condition_code_regs
+
+/* Define this to return an RTX representing the place where a
+   function returns or receives a value of data type RET_TYPE, a tree
+   node node representing a data type.  */
+#undef TARGET_FUNCTION_VALUE
+#define TARGET_FUNCTION_VALUE moxie_function_value
+
+struct gcc_target targetm = TARGET_INITIALIZER;
+
+#include "gt-moxie.h"
diff --git a/gcc/config/moxie/moxie.h b/gcc/config/moxie/moxie.h
new file mode 100644
index 0000000000000000000000000000000000000000..6685b0941eabbab5c34797939728138e2cd569fb
--- /dev/null
+++ b/gcc/config/moxie/moxie.h
@@ -0,0 +1,574 @@
+/* Target Definitions for moxie.
+   Copyright (C) 2008, 2009  Free Software Foundation, Inc.
+   Contributed by Anthony Green.
+
+   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/>.  */
+
+#ifndef GCC_MOXIE_H
+#define GCC_MOXIE_H
+
+/* This is defined by svr4.h, which is included prior to this file.
+   However, we should undefine it for moxie-elf, since we don't provide
+   functions like access() and mkdir() in newlib.  This will have to
+   be defined again for a Linux port.  */
+#undef TARGET_POSIX_IO
+
+/* Another C string constant used much like `LINK_SPEC'.  The difference
+   between the two is that `STARTFILE_SPEC' is used at the very beginning of
+   the command given to the linker.
+
+   If this macro is not defined, a default is provided that loads the standard
+   C startup file from the usual place.  See `gcc.c'.
+
+   Defined in svr4.h.  */
+#undef  STARTFILE_SPEC
+#define STARTFILE_SPEC "crt0%O%s crti.o%s crtbegin.o%s"
+
+/* Provide an ENDFILE_SPEC appropriate for svr4.  Here we tack on our own
+   magical crtend.o file (see crtstuff.c) which provides part of the
+   support for getting C++ file-scope static object constructed before
+   entering `main', followed by the normal svr3/svr4 "finalizer" file,
+   which is either `gcrtn.o' or `crtn.o'.  */
+
+#undef  ENDFILE_SPEC
+#define ENDFILE_SPEC "crtend.o%s crtn.o%s"
+
+/* Provide a LIB_SPEC appropriate for svr4.  Here we tack on the default
+   standard C library (unless we are building a shared library) and
+   the simulator BSP code.  */
+
+#undef LIB_SPEC
+#define LIB_SPEC "%{!shared:%{!symbolic:-lc}}"
+
+/* Layout of Source Language Data Types */
+
+#define INT_TYPE_SIZE 32
+#define SHORT_TYPE_SIZE 16
+#define LONG_TYPE_SIZE 32
+#define LONG_LONG_TYPE_SIZE 64
+
+#define FLOAT_TYPE_SIZE 32
+#define DOUBLE_TYPE_SIZE 64
+#define LONG_DOUBLE_TYPE_SIZE 64
+
+#define DEFAULT_SIGNED_CHAR 1
+
+/* Registers...
+
+   $fp  - frame pointer
+   $sp  - stack pointer
+   $r0  - general purpose 32-bit register.
+   $r1  - general purpose 32-bit register.
+   $r2  - general purpose 32-bit register.
+   $r3  - general purpose 32-bit register.
+   $r4  - general purpose 32-bit register.
+   $r5  - general purpose 32-bit register.
+   $r6  - general purpose 32-bit register.
+   $r7  - general purpose 32-bit register.
+   $r8  - general purpose 32-bit register.
+   $r9  - general purpose 32-bit register.
+   $r10 - general purpose 32-bit register.
+   $r11 - general purpose 32-bit register.
+   $r12 - general purpose 32-bit register.
+   $r13 - reserved for execution environment.
+
+   Special Registers...
+
+   $pc - 32-bit program counter.
+   
+*/
+
+#define REGISTER_NAMES {	\
+  "$fp", "$sp", "$r0", "$r1",   \
+  "$r2", "$r3", "$r4", "$r5",   \
+  "$r6", "$r7", "$r8", "$r9",   \
+  "$r10", "$r11", "$r12", "$r13",   \
+  "?fp", "?ap", "$pc", "?cc" }
+
+#define MOXIE_FP     0
+#define MOXIE_SP     1
+#define MOXIE_R0     2
+#define MOXIE_R1     3 
+#define MOXIE_R2     4
+#define MOXIE_R3     5
+#define MOXIE_R4     6
+#define MOXIE_R5     7
+#define MOXIE_R6     8
+#define MOXIE_R7     9
+#define MOXIE_R8     10
+#define MOXIE_R9     11
+#define MOXIE_R10    12
+#define MOXIE_R11    13
+#define MOXIE_R12    14
+#define MOXIE_R13    15
+#define MOXIE_QFP    16
+#define MOXIE_QAP    17
+#define MOXIE_PC     18
+#define MOXIE_CC     19
+
+#define FIRST_PSEUDO_REGISTER 20
+
+enum reg_class
+{
+  NO_REGS,
+  GENERAL_REGS,
+  SPECIAL_REGS,
+  CC_REG,
+  ALL_REGS,
+  LIM_REG_CLASSES
+};
+
+
+/* The following macro defines cover classes for Integrated Register
+   Allocator.  Cover classes is a set of non-intersected register
+   classes covering all hard registers used for register allocation
+   purpose.  Any move between two registers of a cover class should be
+   cheaper than load or store of the registers.  The macro value is
+   array of register classes with LIM_REG_CLASSES used as the end
+   marker.  */
+#define IRA_COVER_CLASSES { GENERAL_REGS, LIM_REG_CLASSES }
+
+#define REG_CLASS_CONTENTS \
+{ { 0x00000000 }, /* Empty */			   \
+  { 0x0003FFFF }, /* $fp, $sp, $r0 to $r5, ?fp */  \
+  { 0x00040000 }, /* $pc */	                   \
+  { 0x00080000 }, /* ?cc */                        \
+  { 0x000FFFFF }  /* All registers */              \
+}
+
+#define N_REG_CLASSES LIM_REG_CLASSES
+
+#define REG_CLASS_NAMES {\
+    "NO_REGS", \
+    "GENERAL_REGS", \
+    "SPECIAL_REGS", \
+    "CC_REG", \
+    "ALL_REGS" }
+
+#define FIXED_REGISTERS     { 1, 1, 0, 0, \
+			      0, 0, 0, 0, \
+			      0, 0, 0, 0, \
+			      0, 0, 0, 1, \
+                              1, 1, 1, 1 }
+
+#define CALL_USED_REGISTERS { 1, 1, 1, 1, \
+			      0, 0, 0, 0, \
+			      0, 0, 0, 0, \
+			      0, 0, 1, 1, \
+                              1, 1, 1, 1 }
+
+/* We can't copy to or from our CC register. */
+#define AVOID_CCMODE_COPIES 1
+
+/* A C expression that is nonzero if it is permissible to store a
+   value of mode MODE in hard register number REGNO (or in several
+   registers starting with that one).  All gstore registers are 
+   equivalent, so we can set this to 1.  */
+#define HARD_REGNO_MODE_OK(R,M) 1
+
+/* A C expression whose value is a register class containing hard
+   register REGNO.  */
+#define REGNO_REG_CLASS(R) ((R < MOXIE_PC) ? GENERAL_REGS : \
+                            (R == MOXIE_CC ? CC_REG : SPECIAL_REGS))
+
+/* A C expression for the number of consecutive hard registers,
+   starting at register number REGNO, required to hold a value of mode
+   MODE.  */
+#define HARD_REGNO_NREGS(REGNO, MODE)			   \
+  ((GET_MODE_SIZE (MODE) + UNITS_PER_WORD - 1)		   \
+   / UNITS_PER_WORD)
+
+/* A C expression that is nonzero if a value of mode MODE1 is
+   accessible in mode MODE2 without copying.  */
+#define MODES_TIEABLE_P(MODE1, MODE2) 1
+
+/* A C expression for the maximum number of consecutive registers of
+   class CLASS needed to hold a value of mode MODE.  */
+#define CLASS_MAX_NREGS(CLASS, MODE) \
+  ((GET_MODE_SIZE (MODE) + UNITS_PER_WORD - 1) / UNITS_PER_WORD)
+
+/* A C expression that places additional restrictions on the register
+   class to use when it is necessary to copy value X into a register
+   in class CLASS.  */
+#define PREFERRED_RELOAD_CLASS(X,CLASS) CLASS
+
+/* The Overall Framework of an Assembler File */
+
+#undef  ASM_SPEC
+#define ASM_COMMENT_START "#"
+#define ASM_APP_ON ""
+#define ASM_APP_OFF ""
+
+#define FILE_ASM_OP     "\t.file\n"
+
+/* Switch to the text or data segment.  */
+#define TEXT_SECTION_ASM_OP  "\t.text"
+#define DATA_SECTION_ASM_OP  "\t.data"
+
+/* Assembler Commands for Alignment */
+
+#define ASM_OUTPUT_ALIGN(STREAM,POWER) \
+	fprintf (STREAM, "\t.p2align\t%d\n", POWER);
+
+/* A C compound statement to output to stdio stream STREAM the
+   assembler syntax for an instruction operand X.  */
+#define PRINT_OPERAND(STREAM, X, CODE) moxie_print_operand (STREAM, X, CODE)
+
+#define PRINT_OPERAND_ADDRESS(STREAM ,X) moxie_print_operand_address (STREAM, X)
+
+/* Output and Generation of Labels */
+
+#define GLOBAL_ASM_OP "\t.global\t"
+
+/* Passing Arguments in Registers */
+
+/* A C expression that controls whether a function argument is passed
+   in a register, and which register.  */
+#define FUNCTION_ARG(CUM,MODE,TYPE,NAMED) \
+  moxie_function_arg(CUM,MODE,TYPE,NAMED)
+
+/* A C type for declaring a variable that is used as the first
+   argument of `FUNCTION_ARG' and other related values.  */
+#define CUMULATIVE_ARGS unsigned int
+
+/* If defined, the maximum amount of space required for outgoing arguments
+   will be computed and placed into the variable
+   `current_function_outgoing_args_size'.  No space will be pushed
+   onto the stack for each call; instead, the function prologue should
+   increase the stack frame size by this amount.  */
+#define ACCUMULATE_OUTGOING_ARGS 1
+
+/* A C statement (sans semicolon) for initializing the variable CUM
+   for the state at the beginning of the argument list.  
+   For moxie, the first arg is passed in register 2 (aka $r0).  */
+#define INIT_CUMULATIVE_ARGS(CUM,FNTYPE,LIBNAME,FNDECL,N_NAMED_ARGS) \
+  (CUM = MOXIE_R0)
+
+#define MOXIE_FUNCTION_ARG_SIZE(MODE, TYPE)	\
+  ((MODE) != BLKmode ? GET_MODE_SIZE (MODE)	\
+   : (unsigned) int_size_in_bytes (TYPE))
+
+#define FUNCTION_ARG_ADVANCE(CUM,MODE,TYPE,NAMED) \
+  (CUM = (CUM < MOXIE_R2 ?                        \
+          CUM + ((3 + MOXIE_FUNCTION_ARG_SIZE(MODE,TYPE))/4) : CUM ))
+
+/* How Scalar Function Values Are Returned */
+
+/* These macros are deprecated, but we still need them for now since
+   the version of gcc we're using doesn't fully support
+   TARGET_FUNCTION_VALUE.  */
+#define FUNCTION_VALUE(VALTYPE, FUNC) \
+  moxie_function_value (VALTYPE, FUNC, 0)
+#define FUNCTION_OUTGOING_VALUE(VALTYPE, FUNC) \
+  moxie_function_value (VALTYPE, FUNC, 1)
+
+/* A C expression to create an RTX representing the place where a
+   library function returns a value of mode MODE.  */
+#define LIBCALL_VALUE(MODE) gen_rtx_REG (MODE, 2)
+
+/* STACK AND CALLING */
+
+/* Define this macro if pushing a word onto the stack moves the stack
+   pointer to a smaller address.  */
+#define STACK_GROWS_DOWNWARD
+
+#define INITIAL_FRAME_POINTER_OFFSET(DEPTH) (DEPTH) = 0
+
+/* Offset from the frame pointer to the first local variable slot to
+   be allocated.  */
+#define STARTING_FRAME_OFFSET 0
+
+/* Define this if the above stack space is to be considered part of the
+   space allocated by the caller.  */
+#define OUTGOING_REG_PARM_STACK_SPACE(FNTYPE) 1
+#define STACK_PARMS_IN_REG_PARM_AREA
+
+/* Define this if it is the responsibility of the caller to allocate
+   the area reserved for arguments passed in registers.  */
+#define REG_PARM_STACK_SPACE(FNDECL) (2 * UNITS_PER_WORD)
+
+/* Offset from the argument pointer register to the first argument's
+   address.  On some machines it may depend on the data type of the
+   function.  */
+#define FIRST_PARM_OFFSET(F) 12
+
+/* Define this macro to nonzero value if the addresses of local variable slots
+   are at negative offsets from the frame pointer.  */
+#define FRAME_GROWS_DOWNWARD 1
+
+/* Define this macro as a C expression that is nonzero for registers that are
+   used by the epilogue or the return pattern.  The stack and frame
+   pointer registers are already assumed to be used as needed.  */
+#define EPILOGUE_USES(R) (R == MOXIE_R5)
+
+#define OVERRIDE_OPTIONS moxie_override_options ()
+
+/* Storage Layout */
+
+#define BITS_BIG_ENDIAN 0
+#define BYTES_BIG_ENDIAN 1
+#define WORDS_BIG_ENDIAN 1
+
+/* Alignment required for a function entry point, in bits.  */
+#define FUNCTION_BOUNDARY 16
+
+/* Define this macro as a C expression which is nonzero if accessing
+   less than a word of memory (i.e. a `char' or a `short') is no
+   faster than accessing a word of memory.  */
+#define SLOW_BYTE_ACCESS 1
+
+/* Number of storage units in a word; normally the size of a
+   general-purpose register, a power of two from 1 or 8.  */
+#define UNITS_PER_WORD 4
+
+/* Define this macro to the minimum alignment enforced by hardware
+   for the stack pointer on this machine.  The definition is a C
+   expression for the desired alignment (measured in bits).  */
+#define STACK_BOUNDARY 32
+
+/* Normal alignment required for function parameters on the stack, in
+   bits.  All stack parameters receive at least this much alignment
+   regardless of data type.  */
+#define PARM_BOUNDARY 32
+
+/* Alignment of field after `int : 0' in a structure.  */
+#define EMPTY_FIELD_BOUNDARY  32
+
+/* No data type wants to be aligned rounder than this.  */
+#define BIGGEST_ALIGNMENT 32
+
+/* The best alignment to use in cases where we have a choice.  */
+#define FASTEST_ALIGNMENT 32
+
+/* Every structures size must be a multiple of 8 bits.  */
+#define STRUCTURE_SIZE_BOUNDARY 8
+
+/* Look at the fundamental type that is used for a bit-field and use 
+   that to impose alignment on the enclosing structure.
+   struct s {int a:8}; should have same alignment as "int", not "char".  */
+#define	PCC_BITFIELD_TYPE_MATTERS	1
+
+/* Largest integer machine mode for structures.  If undefined, the default
+   is GET_MODE_SIZE(DImode).  */
+#define MAX_FIXED_MODE_SIZE 32
+
+/* Make strings word-aligned so strcpy from constants will be faster.  */
+#define CONSTANT_ALIGNMENT(EXP, ALIGN)  \
+  ((TREE_CODE (EXP) == STRING_CST	\
+    && (ALIGN) < FASTEST_ALIGNMENT)	\
+   ? FASTEST_ALIGNMENT : (ALIGN))
+
+/* Make arrays of chars word-aligned for the same reasons.  */
+#define DATA_ALIGNMENT(TYPE, ALIGN)		\
+  (TREE_CODE (TYPE) == ARRAY_TYPE		\
+   && TYPE_MODE (TREE_TYPE (TYPE)) == QImode	\
+   && (ALIGN) < FASTEST_ALIGNMENT ? FASTEST_ALIGNMENT : (ALIGN))
+     
+/* Set this nonzero if move instructions will actually fail to work
+   when given unaligned data.  */
+#define STRICT_ALIGNMENT 1
+
+/* Generating Code for Profiling */
+#define FUNCTION_PROFILER(FILE,LABELNO) (abort (), 0)
+
+/* Trampolines for Nested Functions.  */
+#define TRAMPOLINE_SIZE (2 + 6 + 6 + 2 + 6)
+
+/* Alignment required for trampolines, in bits.  */
+#define TRAMPOLINE_ALIGNMENT 16
+
+/* A C statement to initialize the variable parts of a trampoline.  ADDR is an
+   RTX for the address of the trampoline; FNADDR is an RTX for the address of
+   the nested function; STATIC_CHAIN is an RTX for the static chain value that
+   should be passed to the function when it is called.  */
+#define INITIALIZE_TRAMPOLINE(ADDR, FNADDR, STATIC_CHAIN)		      \
+do									      \
+{									      \
+  emit_move_insn (gen_rtx_MEM (SImode,                                        \
+                               plus_constant (ADDR, 4)), STATIC_CHAIN);       \
+  emit_move_insn (gen_rtx_MEM (SImode, plus_constant (ADDR, 18)), FNADDR);    \
+} while (0);
+
+/* A C statement to output, on the stream FILE, assembler code for a
+   block of data that contains the constant parts of a trampoline.
+   This code should not include a label--the label is taken care of
+   automatically.  */
+#define TRAMPOLINE_TEMPLATE(FILE)	       	\
+{						\
+  fprintf (FILE, "\tpush  $sp, $r0\n");         \
+  fprintf (FILE, "\tldi.l $r0, 0x0\n"); 	\
+  fprintf (FILE, "\tsto.l 0x8($fp), $r0\n");	\
+  fprintf (FILE, "\tpop   $sp, $r0\n");		\
+  fprintf (FILE, "\tjmpa  0x0\n");	        \
+}
+
+/* An alias for the machine mode for pointers.  */
+#define Pmode         SImode
+
+/* An alias for the machine mode used for memory references to
+   functions being called, in `call' RTL expressions.  */
+#define FUNCTION_MODE QImode
+
+/* The register number of the stack pointer register, which must also
+   be a fixed register according to `FIXED_REGISTERS'.  */
+#define STACK_POINTER_REGNUM 1
+
+/* The register number of the frame pointer register, which is used to
+   access automatic variables in the stack frame.  */
+#define FRAME_POINTER_REGNUM MOXIE_QFP
+
+/* The register number of the arg pointer register, which is used to
+   access the function's argument list.  */
+#define ARG_POINTER_REGNUM MOXIE_QAP
+
+/* If the static chain is passed in memory, these macros provide rtx
+   giving 'mem' expressions that denote where they are stored.
+   'STATIC_CHAIN' and 'STATIC_CHAIN_INCOMING' give the locations as
+   seen by the calling and called functions, respectively.  */
+
+#define STATIC_CHAIN							\
+  gen_rtx_MEM (Pmode, plus_constant (stack_pointer_rtx, -UNITS_PER_WORD))
+
+#define STATIC_CHAIN_INCOMING						\
+  gen_rtx_MEM (Pmode, plus_constant (arg_pointer_rtx, 2 * UNITS_PER_WORD))
+
+#define HARD_FRAME_POINTER_REGNUM MOXIE_FP
+
+#if 0
+#define ELIMINABLE_REGS							\
+{{ FRAME_POINTER_REGNUM, STACK_POINTER_REGNUM },			\
+ { FRAME_POINTER_REGNUM, HARD_FRAME_POINTER_REGNUM },			\
+ { ARG_POINTER_REGNUM,	 STACK_POINTER_REGNUM },			\
+ { ARG_POINTER_REGNUM,   HARD_FRAME_POINTER_REGNUM }}			
+#else
+#define ELIMINABLE_REGS							\
+{{ FRAME_POINTER_REGNUM, HARD_FRAME_POINTER_REGNUM },			\
+ { ARG_POINTER_REGNUM,   HARD_FRAME_POINTER_REGNUM }}			
+#endif
+
+/* A C expression that returns nonzero if the compiler is allowed to
+   try to replace register number FROM-REG with register number
+   TO-REG.  This macro need only be defined if `ELIMINABLE_REGS' is
+   defined, and will usually be the constant 1, since most of the
+   cases preventing register elimination are things that the compiler
+   already knows about.  */
+#define CAN_ELIMINATE(FROM, TO) 1
+
+/* This macro is similar to `INITIAL_FRAME_POINTER_OFFSET'.  It
+   specifies the initial difference between the specified pair of
+   registers.  This macro must be defined if `ELIMINABLE_REGS' is
+   defined.  */
+#define INITIAL_ELIMINATION_OFFSET(FROM, TO, OFFSET)			\
+  do {									\
+    (OFFSET) = moxie_initial_elimination_offset ((FROM), (TO));		\
+  } while (0)
+
+/* A C expression that is nonzero if REGNO is the number of a hard
+   register in which function arguments are sometimes passed.  */
+#define FUNCTION_ARG_REGNO_P(r) (r == MOXIE_R0 || r == MOXIE_R1)
+
+/* A C expression that is nonzero if REGNO is the number of a hard
+   register in which the values of called function may come back.  */
+#define FUNCTION_VALUE_REGNO_P(r) (r == MOXIE_R0)
+
+/* A macro whose definition is the name of the class to which a valid
+   base register must belong.  A base register is one used in an
+   address which is the register value plus a displacement.  */
+#define BASE_REG_CLASS GENERAL_REGS
+
+#define INDEX_REG_CLASS NO_REGS
+
+#define HARD_REGNO_OK_FOR_BASE_P(NUM) \
+  ((NUM) >= 0 && (NUM) < FIRST_PSEUDO_REGISTER \
+   && (REGNO_REG_CLASS(NUM) == GENERAL_REGS \
+       || (NUM) == HARD_FRAME_POINTER_REGNUM))
+
+/* A C expression which is nonzero if register number NUM is suitable
+   for use as a base register in operand addresses.  */
+#ifdef REG_OK_STRICT
+#define REGNO_OK_FOR_BASE_P(NUM)		 \
+  (HARD_REGNO_OK_FOR_BASE_P(NUM) 		 \
+   || HARD_REGNO_OK_FOR_BASE_P(reg_renumber[(NUM)]))
+#else
+#define REGNO_OK_FOR_BASE_P(NUM)		 \
+  ((NUM) >= FIRST_PSEUDO_REGISTER || HARD_REGNO_OK_FOR_BASE_P(NUM))
+#endif
+
+/* A C expression which is nonzero if register number NUM is suitable
+   for use as an index register in operand addresses.  */
+#define REGNO_OK_FOR_INDEX_P(NUM) MOXIE_FP
+
+/* The maximum number of bytes that a single instruction can move
+   quickly between memory and registers or between two memory
+   locations.  */
+#define MOVE_MAX 4
+#define TRULY_NOOP_TRUNCATION(op,ip) 1
+
+#define RETURN_POPS_ARGS(FUNDECL, FUNTYPE, STACK_SIZE) 0
+
+/* A C expression that is nonzero if X is a legitimate constant for
+   an immediate operand on the target machine.  */
+#define LEGITIMATE_CONSTANT_P(X) 1
+
+#define FRAME_POINTER_REQUIRED 1
+
+/* A C expression that is 1 if the RTX X is a constant which is a
+   valid address.  */
+#define CONSTANT_ADDRESS_P(X) CONSTANT_P(X)
+
+/* A number, the maximum number of registers that can appear in a
+   valid memory address.  */
+#define MAX_REGS_PER_ADDRESS 1
+
+#define TRULY_NOOP_TRUNCATION(op,ip) 1
+
+/* An alias for a machine mode name.  This is the machine mode that
+   elements of a jump-table should have.  */
+#define CASE_VECTOR_MODE SImode
+
+/* A C compound statement with a conditional `goto LABEL;' executed
+   if X (an RTX) is a legitimate memory address on the target machine
+   for a memory operand of mode MODE.  */
+#define GO_IF_LEGITIMATE_ADDRESS(MODE,X,LABEL)		\
+  do {                                                  \
+    if (GET_CODE(X) == PLUS)				\
+      {							\
+	rtx op1,op2;					\
+	op1 = XEXP(X,0);				\
+	op2 = XEXP(X,1);				\
+	if (GET_CODE(op1) == REG			\
+	    && CONSTANT_ADDRESS_P(op2)			\
+	    && REGNO_OK_FOR_BASE_P(REGNO(op1)))		\
+	  goto LABEL;					\
+      }							\
+    if (REG_P (X) && REGNO_OK_FOR_BASE_P (REGNO (X)))	\
+      goto LABEL;					\
+    if (GET_CODE (X) == SYMBOL_REF			\
+	|| GET_CODE (X) == LABEL_REF			\
+	|| GET_CODE (X) == CONST)			\
+      goto LABEL;					\
+  } while (0)
+
+/* Run-time Target Specification */
+
+#define TARGET_CPU_CPP_BUILTINS() \
+  { \
+    builtin_define_std ("moxie");		\
+    builtin_define_std ("MOXIE");		\
+  }
+
+#endif /* GCC_MOXIE_H */
diff --git a/gcc/config/moxie/moxie.md b/gcc/config/moxie/moxie.md
new file mode 100644
index 0000000000000000000000000000000000000000..713bd4523d099ae22419e33b7441a959a386f6d0
--- /dev/null
+++ b/gcc/config/moxie/moxie.md
@@ -0,0 +1,421 @@
+;; Machine description for Moxie
+;; Copyright (C) 2009 Free Software Foundation, Inc.
+;; Contributed by Anthony Green <green@moxielogic.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/>.
+
+;; -------------------------------------------------------------------------
+;; Moxie specific constraints
+;; -------------------------------------------------------------------------
+
+(include "constraints.md")
+(include "predicates.md")
+
+;; -------------------------------------------------------------------------
+;; nop instruction
+;; -------------------------------------------------------------------------
+
+(define_insn "nop"
+  [(const_int 0)]
+  ""
+  "nop")
+
+;; -------------------------------------------------------------------------
+;; Arithmetic instructions
+;; -------------------------------------------------------------------------
+
+(define_insn "addsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r,r,r")
+	  (plus:SI
+	   (match_operand:SI 1 "register_operand" "0,0,0")
+	   (match_operand:SI 2 "moxie_add_operand" "I,N,r")))]
+  ""
+  "@
+  inc    %0, %2
+  dec	 %0, -%2
+  add.l  %0, %2")
+
+(define_insn "subsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r,r")
+	  (minus:SI
+	   (match_operand:SI 1 "register_operand" "0,0")
+	   (match_operand:SI 2 "moxie_sub_operand" "I,r")))]
+  ""
+  "@
+  dec    %0, %2
+  sub.l  %0, %2")
+
+(define_insn "mulsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	  (mult:SI
+	   (match_operand:SI 1 "register_operand" "0")
+	   (match_operand:SI 2 "register_operand" "r")))]
+  ""
+  "mul.l  %0, %2")
+
+(define_insn "divsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	  (div:SI
+	   (match_operand:SI 1 "register_operand" "0")
+	   (match_operand:SI 2 "register_operand" "r")))]
+  ""
+  "div.l  %0, %2")
+
+(define_insn "udivsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	  (udiv:SI
+	   (match_operand:SI 1 "register_operand" "0")
+	   (match_operand:SI 2 "register_operand" "r")))]
+  ""
+  "udiv.l %0, %2")
+
+(define_insn "modsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	  (mod:SI
+	   (match_operand:SI 1 "register_operand" "0")
+	   (match_operand:SI 2 "register_operand" "r")))]
+  ""
+  "mod.l  %0, %2")
+
+(define_insn "umodsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	  (umod:SI
+	   (match_operand:SI 1 "register_operand" "0")
+	   (match_operand:SI 2 "register_operand" "r")))]
+  ""
+  "umod.l %0, %2")
+
+;; -------------------------------------------------------------------------
+;; Unary arithmetic instructions
+;; -------------------------------------------------------------------------
+
+(define_insn "negsi2"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	  (neg:SI (match_operand:SI 1 "register_operand" "r")))]
+  ""
+  "neg    %0, %1")
+
+(define_insn "one_cmplsi2"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	(not:SI (match_operand:SI 1 "register_operand" "r")))]
+  ""
+  "not    %0, %1")
+
+;; -------------------------------------------------------------------------
+;; Logical operators
+;; -------------------------------------------------------------------------
+
+(define_insn "andsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	(and:SI (match_operand:SI 1 "register_operand" "0")
+		(match_operand:SI 2 "register_operand" "r")))]
+  ""
+{
+  return "and    %0, %2";
+})
+
+(define_insn "xorsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	(xor:SI (match_operand:SI 1 "register_operand" "0")
+		(match_operand:SI 2 "register_operand" "r")))]
+  ""
+{
+  return "xor    %0, %2";
+})
+
+(define_insn "iorsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	(ior:SI (match_operand:SI 1 "register_operand" "0")
+		(match_operand:SI 2 "register_operand" "r")))]
+  ""
+{
+  return "or     %0, %2";
+})
+
+;; -------------------------------------------------------------------------
+;; Shifters
+;; -------------------------------------------------------------------------
+
+(define_insn "ashlsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	(ashift:SI (match_operand:SI 1 "register_operand" "0")
+		   (match_operand:SI 2 "register_operand" "r")))]
+  ""
+{
+  return "ashl   %0, %2";
+})
+
+(define_insn "ashrsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	(ashiftrt:SI (match_operand:SI 1 "register_operand" "0")
+		     (match_operand:SI 2 "register_operand" "r")))]
+  ""
+{
+  return "ashr   %0, %2";
+})
+
+(define_insn "lshrsi3"
+  [(set (match_operand:SI 0 "register_operand" "=r")
+	(lshiftrt:SI (match_operand:SI 1 "register_operand" "0")
+		     (match_operand:SI 2 "register_operand" "r")))]
+  ""
+{
+  return "lshr   %0, %2";
+})
+
+;; -------------------------------------------------------------------------
+;; Move instructions
+;; -------------------------------------------------------------------------
+
+;; SImode
+
+;; Push a register onto the stack
+(define_insn "movsi_push"
+  [(set:SI (mem:SI (pre_dec:SI (reg:SI 1)))
+	(match_operand:SI 0 "register_operand" "r"))]
+  ""
+  "push   $sp, %0")
+
+;; Pop a register from the stack
+(define_insn "movsi_pop"
+  [(set:SI (match_operand:SI 0 "register_operand" "=r")
+	(mem:SI (post_inc:SI (reg:SI 1))))]
+  ""
+  "pop    $sp, %0")
+
+(define_expand "movsi"
+   [(set (match_operand:SI 0 "general_operand" "")
+ 	(match_operand:SI 1 "general_operand" ""))]
+   ""
+  "
+{
+  /* If this is a store, force the value into a register.  */
+  if (! (reload_in_progress || reload_completed))
+  {
+    if (MEM_P (operands[0]))
+    {
+      operands[1] = force_reg (SImode, operands[1]);
+      if (MEM_P (XEXP (operands[0], 0)))
+        operands[0] = gen_rtx_MEM (SImode, force_reg (SImode, XEXP (operands[0], 0)));
+    }
+    else 
+      if (MEM_P (operands[1])
+          && MEM_P (XEXP (operands[1], 0)))
+        operands[1] = gen_rtx_MEM (SImode, force_reg (SImode, XEXP (operands[1], 0)));
+  }
+}")
+
+(define_insn "*movsi"
+  [(set (match_operand:SI 0 "general_operand" "=r,r,W,A,r,r,B,r")
+	(match_operand:SI 1 "moxie_general_movsrc_operand" "r,i,r,r,W,A,r,B"))]
+  "register_operand (operands[0], SImode)
+   || register_operand (operands[1], SImode)"
+  "@
+   mov    %0, %1
+   ldi.l  %0, %1
+   st.l   %0, %1
+   sta.l  %0, %1
+   ld.l   %0, %1
+   lda.l  %0, %1
+   sto.l  %0, %1
+   ldo.l  %0, %1")
+
+(define_expand "movqi"
+  [(set (match_operand:QI 0 "general_operand" "")
+	(match_operand:QI 1 "general_operand" ""))]
+  ""
+  "
+{
+  /* If this is a store, force the value into a register.  */
+  if (MEM_P (operands[0]))
+    operands[1] = force_reg (QImode, operands[1]);
+}")
+
+(define_insn "*movqi"
+  [(set (match_operand:QI 0 "general_operand" "=r,r,W,A,r,r,B,r")
+	(match_operand:QI 1 "moxie_general_movsrc_operand" "r,i,r,r,W,A,r,B"))]
+  "register_operand (operands[0], QImode)
+   || register_operand (operands[1], QImode)"
+  "@
+   mov    %0, %1
+   ldi.b  %0, %1
+   st.b   %0, %1
+   sta.b  %0, %1
+   ld.b   %0, %1
+   lda.b  %0, %1
+   sto.b  %0, %1
+   ldo.b  %0, %1")
+
+(define_expand "movhi"
+  [(set (match_operand:HI 0 "general_operand" "")
+	(match_operand:HI 1 "general_operand" ""))]
+  ""
+  "
+{
+  /* If this is a store, force the value into a register.  */
+  if (MEM_P (operands[0]))
+    operands[1] = force_reg (HImode, operands[1]);
+}")
+
+(define_insn "*movhi"
+  [(set (match_operand:HI 0 "general_operand" "=r,r,W,A,r,r,B,r")
+	(match_operand:HI 1 "moxie_general_movsrc_operand" "r,i,r,r,W,A,r,B"))]
+  "(register_operand (operands[0], HImode)
+    || register_operand (operands[1], HImode))"
+  "@
+   mov    %0, %1
+   ldi.s  %0, %1
+   st.s   %0, %1
+   sta.s  %0, %1
+   ld.s   %0, %1
+   lda.s  %0, %1
+   sto.s  %0, %1
+   ldo.s  %0, %1")
+
+;; -------------------------------------------------------------------------
+;; Compare instructions
+;; -------------------------------------------------------------------------
+
+(define_constants
+  [(CC_REG 11)])
+
+(define_expand "cbranchsi4"
+  [(set (reg:CC CC_REG)
+        (compare:CC
+         (match_operand:SI 1 "register_operand" "")
+         (match_operand:SI 2 "register_operand" "")))
+   (set (pc)
+        (if_then_else (match_operator:CC 0 "comparison_operator"
+                       [(reg:CC CC_REG) (const_int 0)])
+                      (label_ref (match_operand 3 "" ""))
+                      (pc)))]
+  ""
+  "")
+
+(define_insn "*cmpsi"
+  [(set (reg:CC CC_REG)
+	(compare
+	 (match_operand:SI 0 "register_operand" "r")
+	 (match_operand:SI 1 "register_operand"	"r")))]
+  ""
+  "cmp    %0, %1")
+
+
+;; -------------------------------------------------------------------------
+;; Branch instructions
+;; -------------------------------------------------------------------------
+
+(define_code_iterator cond [ne eq lt ltu gt gtu ge le geu leu])
+(define_code_attr CC [(ne "ne") (eq "eq") (lt "lt") (ltu "ltu") 
+		      (gt "gt") (gtu "gtu") (ge "ge") (le "le") 
+		      (geu "geu") (leu "leu") ])
+
+(define_insn "*b<cond:code>"
+  [(set (pc)
+	(if_then_else (cond (reg:CC CC_REG)
+			    (const_int 0))
+		      (label_ref (match_operand 0 "" ""))
+		      (pc)))]
+  ""
+  "b<CC>   %l0")
+
+;; -------------------------------------------------------------------------
+;; Call and Jump instructions
+;; -------------------------------------------------------------------------
+
+(define_expand "call"
+  [(call (match_operand:QI 0 "memory_operand" "")
+		(match_operand 1 "general_operand" ""))]
+  ""
+{
+  gcc_assert (MEM_P (operands[0]));
+})
+
+(define_insn "*call"
+  [(call (mem:QI (match_operand:SI
+		  0 "nonmemory_operand" "i,r"))
+	 (match_operand 1 "" ""))]
+  ""
+  "@
+   jsra   %0
+   jsr    %0")
+
+(define_expand "call_value"
+  [(set (match_operand 0 "" "")
+		(call (match_operand:QI 1 "memory_operand" "")
+		 (match_operand 2 "" "")))]
+  ""
+{
+  gcc_assert (MEM_P (operands[1]));
+})
+
+(define_insn "*call_value"
+  [(set (match_operand 0 "register_operand" "=r")
+	(call (mem:QI (match_operand:SI
+		       1 "immediate_operand" "i"))
+	      (match_operand 2 "" "")))]
+  ""
+  "jsra   %1")
+
+(define_insn "*call_value_indirect"
+  [(set (match_operand 0 "register_operand" "=r")
+	(call (mem:QI (match_operand:SI
+		       1 "register_operand" "r"))
+	      (match_operand 2 "" "")))]
+  ""
+  "jsr    %1")
+
+(define_insn "indirect_jump"
+  [(set (pc) (match_operand:SI 0 "nonimmediate_operand" "r"))]
+  ""
+  "jmp    %0")
+
+(define_insn "jump"
+  [(set (pc)
+	(label_ref (match_operand 0 "" "")))]
+  ""
+  "jmpa   %l0")
+
+
+;; -------------------------------------------------------------------------
+;; Prologue & Epilogue
+;; -------------------------------------------------------------------------
+
+(define_expand "prologue"
+  [(clobber (const_int 0))]
+  ""
+  "
+{
+  moxie_expand_prologue ();
+  DONE;
+}
+")
+
+(define_expand "epilogue"
+  [(return)]
+  ""
+  "
+{
+  moxie_expand_epilogue ();
+  DONE;
+}
+")
+
+(define_insn "returner"
+  [(return)]
+  "reload_completed"
+  "ret")
diff --git a/gcc/config/moxie/predicates.md b/gcc/config/moxie/predicates.md
new file mode 100644
index 0000000000000000000000000000000000000000..f0595c011791c06935c791728b104262a4c9438f
--- /dev/null
+++ b/gcc/config/moxie/predicates.md
@@ -0,0 +1,55 @@
+;; Predicate definitions for Moxie
+;; Copyright (C) 2009 Free Software Foundation, Inc.
+;; Contributed by Anthony Green <green@moxielogic.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/>.
+
+;; -------------------------------------------------------------------------
+;; Predicates
+;; -------------------------------------------------------------------------
+
+;; Nonzero if OP can be source of a simple move operation.
+
+(define_predicate "moxie_general_movsrc_operand"
+  (match_code "mem,const_int,reg,subreg,symbol_ref,label_ref,const")
+{
+  /* Any (MEM LABEL_REF) is OK.  That is a pc-relative load.  */
+  if (MEM_P (op) && GET_CODE (XEXP (op, 0)) == LABEL_REF)
+    return 1;
+
+  if (MEM_P (op)
+      && GET_CODE (XEXP (op, 0)) == PLUS
+      && GET_CODE (XEXP (XEXP (op, 0), 0)) == REG
+      && GET_CODE (XEXP (XEXP (op, 0), 1)) == CONST)
+    return 1;
+
+  return general_operand (op, mode);
+})
+
+;; Nonzero if OP can be an operand to an add/inc/dec instruction.
+
+(define_predicate "moxie_add_operand"
+  (ior (match_code "reg")
+       (and (match_code "const_int")
+	    (match_test "IN_RANGE (INTVAL (op), -255, 255)"))))
+
+;; Nonzero if OP can be an operand to an sub/dec instruction.
+
+(define_predicate "moxie_sub_operand"
+  (ior (match_code "reg")
+       (and (match_code "const_int")
+	    (match_test "IN_RANGE (INTVAL (op), 0, 255)"))))
\ No newline at end of file
diff --git a/gcc/config/moxie/sfp-machine.h b/gcc/config/moxie/sfp-machine.h
new file mode 100644
index 0000000000000000000000000000000000000000..57f515e9fc6c180a80d91e067c0ec4977e57fb3b
--- /dev/null
+++ b/gcc/config/moxie/sfp-machine.h
@@ -0,0 +1,52 @@
+#define _FP_W_TYPE_SIZE		32
+#define _FP_W_TYPE		unsigned long
+#define _FP_WS_TYPE		signed long
+#define _FP_I_TYPE		long
+
+#define _FP_MUL_MEAT_S(R,X,Y)				\
+  _FP_MUL_MEAT_1_wide(_FP_WFRACBITS_S,R,X,Y,umul_ppmm)
+#define _FP_MUL_MEAT_D(R,X,Y)				\
+  _FP_MUL_MEAT_2_wide(_FP_WFRACBITS_D,R,X,Y,umul_ppmm)
+#define _FP_MUL_MEAT_Q(R,X,Y)				\
+  _FP_MUL_MEAT_4_wide(_FP_WFRACBITS_Q,R,X,Y,umul_ppmm)
+
+#define _FP_DIV_MEAT_S(R,X,Y)	_FP_DIV_MEAT_1_loop(S,R,X,Y)
+#define _FP_DIV_MEAT_D(R,X,Y)	_FP_DIV_MEAT_2_udiv(D,R,X,Y)
+#define _FP_DIV_MEAT_Q(R,X,Y)	_FP_DIV_MEAT_4_udiv(Q,R,X,Y)
+
+#define _FP_NANFRAC_S		((_FP_QNANBIT_S << 1) - 1)
+#define _FP_NANFRAC_D		((_FP_QNANBIT_D << 1) - 1), -1
+#define _FP_NANFRAC_Q		((_FP_QNANBIT_Q << 1) - 1), -1, -1, -1
+#define _FP_NANSIGN_S		0
+#define _FP_NANSIGN_D		0
+#define _FP_NANSIGN_Q		0
+
+#define _FP_KEEPNANFRACP 1
+
+/* Someone please check this.  */
+#define _FP_CHOOSENAN(fs, wc, R, X, Y, OP)			\
+  do {								\
+    if ((_FP_FRAC_HIGH_RAW_##fs(X) & _FP_QNANBIT_##fs)		\
+	&& !(_FP_FRAC_HIGH_RAW_##fs(Y) & _FP_QNANBIT_##fs))	\
+      {								\
+	R##_s = Y##_s;						\
+	_FP_FRAC_COPY_##wc(R,Y);				\
+      }								\
+    else							\
+      {								\
+	R##_s = X##_s;						\
+	_FP_FRAC_COPY_##wc(R,X);				\
+      }								\
+    R##_c = FP_CLS_NAN;						\
+  } while (0)
+
+#define	__LITTLE_ENDIAN	1234
+#define	__BIG_ENDIAN	4321
+
+# define __BYTE_ORDER __BIG_ENDIAN
+
+/* Define ALIASNAME as a strong alias for NAME.  */
+# define strong_alias(name, aliasname) _strong_alias(name, aliasname)
+# define _strong_alias(name, aliasname) \
+  extern __typeof (name) aliasname __attribute__ ((alias (#name)));
+
diff --git a/gcc/config/moxie/t-moxie b/gcc/config/moxie/t-moxie
new file mode 100644
index 0000000000000000000000000000000000000000..5498ecbb3543bba8407efda0c10788325006685f
--- /dev/null
+++ b/gcc/config/moxie/t-moxie
@@ -0,0 +1,20 @@
+# Target Makefile Fragment for moxie
+# Copyright (C) 2008  Free Software Foundation, Inc.
+# Contributed by Anthony Green.
+#
+# 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/>.
+
diff --git a/gcc/config/moxie/t-moxie-softfp b/gcc/config/moxie/t-moxie-softfp
new file mode 100644
index 0000000000000000000000000000000000000000..61c575132e9affe66ed4494eb58c7b3e22becb1d
--- /dev/null
+++ b/gcc/config/moxie/t-moxie-softfp
@@ -0,0 +1,9 @@
+softfp_float_modes := sf df
+softfp_int_modes := si di
+softfp_extensions := sfdf
+softfp_truncations := dfsf
+softfp_machine_header := moxie/sfp-machine.h
+softfp_exclude_libgcc2 := y
+
+# softfp seems to be missing a whole bunch of prototypes.
+TARGET_LIBGCC2_CFLAGS += -Wno-missing-prototypes
diff --git a/gcc/doc/contrib.texi b/gcc/doc/contrib.texi
index f8f09be0afb824b4f491a73d35ca4b084e0f1ba0..1545bcbcd60d757136c732061af7f157b100ccba 100644
--- a/gcc/doc/contrib.texi
+++ b/gcc/doc/contrib.texi
@@ -316,7 +316,8 @@ support, improved leaf function register allocation, and his direction
 via the steering committee.
 
 @item
-Anthony Green for his @option{-Os} contributions and Java front end work.
+Anthony Green for his @option{-Os} contributions, the moxie port, and
+Java front end work.
 
 @item
 Stu Grossman for gdb hacking, allowing GCJ developers to debug Java code.
diff --git a/gcc/doc/install.texi b/gcc/doc/install.texi
index 59526f920bda6ee3734e648243f679ccb14df8d1..0804ae3201fdf747a5f7084583cf61b809d16a26 100644
--- a/gcc/doc/install.texi
+++ b/gcc/doc/install.texi
@@ -3759,6 +3759,13 @@ and in order to build GCC for such targets you need to configure with
 See @uref{http://freeware.sgi.com/} for more
 information about using GCC on IRIX platforms.
 
+@html
+<hr />
+@end html
+@heading @anchor{moxie-x-elf}moxie-*-elf
+The moxie processor.  See @uref{http://moxielogic.org/} for more
+information about this processor.
+
 @html
 <hr />
 @end html
diff --git a/gcc/doc/md.texi b/gcc/doc/md.texi
index f91d6e12480bec5b1d9eba291842c402207cd986..065529fdf038b91709fcc4c900760f9fc5109216 100644
--- a/gcc/doc/md.texi
+++ b/gcc/doc/md.texi
@@ -2730,6 +2730,25 @@ Constants in the range @minus{}8 to 2
 
 @end table
 
+@item Moxie---@file{config/moxie/constraints.md}
+@table @code
+@item A
+An absolute address
+
+@item B
+An offset address
+
+@item W
+A register indirect memory operand
+
+@item I
+A constant in the range of 0 to 255.
+
+@item N
+A constant in the range of 0 to -255.
+
+@end table
+
 @need 1000
 @item SPARC---@file{config/sparc/sparc.h}
 @table @code
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 7ac14c0badd3852bdd6a5236691eeeedf2041054..d23e58e60097e640cf79cc28d818bbd902d71f30 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2009-06-10  Anthony Green  <green@moxielogic.com>
+
+	* testsuite/lib/target-supports.exp (check_profiling_available):
+	Profiling is not available for testing purposes on moxie.
+
 2009-06-09  Ian Lance Taylor  <iant@google.com>
 
 	* gcc.dg/Wcxx-compat-12.c: New testcase.
diff --git a/gcc/testsuite/lib/target-supports.exp b/gcc/testsuite/lib/target-supports.exp
index e2da9b0b73d8e4a8b9e92c432184476c7e3038a8..24d814894095b6853175d8d315a03d1a719f997b 100644
--- a/gcc/testsuite/lib/target-supports.exp
+++ b/gcc/testsuite/lib/target-supports.exp
@@ -499,6 +499,7 @@ proc check_profiling_available { test_what } {
 	     || [istarget m68k-*-elf]
 	     || [istarget m68k-*-uclinux*]
 	     || [istarget mips*-*-elf*]
+	     || [istarget moxie-*-elf*]
 	     || [istarget xstormy16-*]
 	     || [istarget xtensa*-*-elf]
 	     || [istarget *-*-rtems*]
diff --git a/libgcc/ChangeLog b/libgcc/ChangeLog
index 38eac131b7f84aae96e4c28c20e56ec387e8f9d1..48053b36a7bf0c6e58315b1df07ea2ff125164e4 100644
--- a/libgcc/ChangeLog
+++ b/libgcc/ChangeLog
@@ -1,3 +1,8 @@
+2009-05-31  Anthony Green  <green@moxielogic.com>
+
+	* config.host: Add moxie support.
+	* config/moxie/t-moxie: New file.
+
 2009-05-29  David Billinghurst <billingd@gcc.gnu.org>
 
 	* config.host: Add i386/${host_address}/t-fprules-softfp and
diff --git a/libgcc/config.host b/libgcc/config.host
index e5e384d23caaaaca6fe31229a20c658af81b9584..cdb274e4216acaa6d4e891883f4f30c27caac2c2 100644
--- a/libgcc/config.host
+++ b/libgcc/config.host
@@ -84,6 +84,8 @@ fido-*-*)
 	;;
 frv*)	cpu_type=frv
 	;;
+moxie*)	cpu_type=moxie
+	;;
 i[34567]86-*-*)
 	cpu_type=i386
 	;;
@@ -415,6 +417,10 @@ mmix-knuth-mmixware)
 	;;
 mn10300-*-*)
 	;;
+moxie-*-*)
+	tmake_file=${cpu_type}/t-moxie
+	extra_parts="crtbegin.o crtend.o crti.o crtn.o"
+	;;
 pdp11-*-*)
 	;;
 picochip-*-*)