[llvm-commits] [dragonegg] r136966 - in /dragonegg/trunk: include/dragonegg/ABI.h include/dragonegg/Internals.h include/dragonegg/Types.h src/Backend.cpp src/Constants.cpp src/Convert.cpp src/Types.cpp

Duncan Sands baldrick at free.fr
Fri Aug 5 02:59:31 PDT 2011


Author: baldrick
Date: Fri Aug  5 04:59:30 2011
New Revision: 136966

URL: http://llvm.org/viewvc/llvm-project?rev=136966&view=rev
Log:
Introduce a Types header for keeping type stuff in.  Move a bunch of stuff
around - no functional change.  Note that this zaps the TypeConverter class,
a pointless class since in spite of appearances it is impossible to have
more than one of them - it's was just a global variable that was pretending
not to be one.

Added:
    dragonegg/trunk/include/dragonegg/Types.h
Modified:
    dragonegg/trunk/include/dragonegg/ABI.h
    dragonegg/trunk/include/dragonegg/Internals.h
    dragonegg/trunk/src/Backend.cpp
    dragonegg/trunk/src/Constants.cpp
    dragonegg/trunk/src/Convert.cpp
    dragonegg/trunk/src/Types.cpp

Modified: dragonegg/trunk/include/dragonegg/ABI.h
URL: http://llvm.org/viewvc/llvm-project/dragonegg/trunk/include/dragonegg/ABI.h?rev=136966&r1=136965&r2=136966&view=diff
==============================================================================
--- dragonegg/trunk/include/dragonegg/ABI.h (original)
+++ dragonegg/trunk/include/dragonegg/ABI.h Fri Aug  5 04:59:30 2011
@@ -29,6 +29,7 @@
 // Plugin headers
 #include "dragonegg/Internals.h"
 #include "dragonegg/Target.h"
+#include "dragonegg/Types.h"
 
 // LLVM headers
 #include "llvm/LLVMContext.h"

Modified: dragonegg/trunk/include/dragonegg/Internals.h
URL: http://llvm.org/viewvc/llvm-project/dragonegg/trunk/include/dragonegg/Internals.h?rev=136966&r1=136965&r2=136966&view=diff
==============================================================================
--- dragonegg/trunk/include/dragonegg/Internals.h (original)
+++ dragonegg/trunk/include/dragonegg/Internals.h Fri Aug  5 04:59:30 2011
@@ -56,7 +56,6 @@
   class Constant;
   class ConstantInt;
   class Type;
-  class FunctionType;
   class TargetMachine;
   class TargetData;
   class DebugInfo;
@@ -174,67 +173,10 @@
 void handleVisibility(tree_node *decl, GlobalValue *GV);
 Twine getLLVMAssemblerName(tree_node *);
 
-struct StructTypeConversionInfo;
-
 /// Return true if and only if field no. N from struct type T is a padding
 /// element added to match llvm struct type size and gcc struct type size.
 bool isPaddingElement(tree_node*, unsigned N);
 
-/// TypeConverter - Implement the converter from GCC types to LLVM types.
-///
-class TypeConverter {
-  /// SCCInProgress - Set of mutually dependent types currently being converted.
-  const std::vector<tree_node*> *SCCInProgress;
-public:
-  TypeConverter() : SCCInProgress(0) {}
-
-  /// ConvertType - Returns the LLVM type to use for memory that holds a value
-  /// of the given GCC type (getRegType should be used for values in registers).
-  Type *ConvertType(tree_node *type);
-
-  /// ConvertFunctionType - Convert the specified FUNCTION_TYPE or METHOD_TYPE
-  /// tree to an LLVM type.  This does the same thing that ConvertType does, but
-  /// it also returns the function's LLVM calling convention and attributes.
-  FunctionType *ConvertFunctionType(tree_node *type,
-                                          tree_node *decl,
-                                          tree_node *static_chain,
-                                          CallingConv::ID &CallingConv,
-                                          AttrListPtr &PAL);
-
-  /// ConvertArgListToFnType - Given a DECL_ARGUMENTS list on an GCC tree,
-  /// return the LLVM type corresponding to the function.  This is useful for
-  /// turning "T foo(...)" functions into "T foo(void)" functions.
-  FunctionType *ConvertArgListToFnType(tree_node *type,
-                                             tree_node *arglist,
-                                             tree_node *static_chain,
-                                             CallingConv::ID &CallingConv,
-                                             AttrListPtr &PAL);
-
-private:
-  Type *ConvertRECORD(tree_node *type);
-  Type *ConvertRecursiveType(tree_node *type);
-  bool DecodeStructFields(tree_node *Field, StructTypeConversionInfo &Info);
-  void DecodeStructBitField(tree_node *Field, StructTypeConversionInfo &Info);
-  void SelectUnionMember(tree_node *type, StructTypeConversionInfo &Info);
-};
-
-extern TypeConverter *TheTypeConverter;
-
-/// getRegType - Returns the LLVM type to use for registers that hold a value
-/// of the scalar GCC type 'type'.  All of the EmitReg* routines use this to
-/// determine the LLVM type to return.
-Type *getRegType(tree_node *type);
-
-/// ConvertType - Returns the LLVM type to use for memory that holds a value
-/// of the given GCC type (getRegType should be used for values in registers).
-inline Type *ConvertType(tree_node *type) {
-  return TheTypeConverter->ConvertType(type);
-}
-
-/// getPointerToType - Returns the LLVM register type to use for a pointer to
-/// the given GCC type.
-Type *getPointerToType(tree_node *type);
-
 /// getDefaultValue - Return the default value to use for a constant or global
 /// that has no value specified.  For example in C like languages such variables
 /// are initialized to zero, while in Ada they hold an undefined value.
@@ -243,45 +185,15 @@
     Constant::getNullValue(Ty) : UndefValue::get(Ty);
 }
 
-/// GetUnitType - Returns an integer one address unit wide if 'NumUnits' is 1;
-/// otherwise returns an array of such integers with 'NumUnits' elements.  For
-/// example, on a machine which has 16 bit bytes returns an i16 or an array of
-/// i16.
-extern Type *GetUnitType(LLVMContext &C, unsigned NumUnits = 1);
-
-/// GetUnitPointerType - Returns an LLVM pointer type which points to memory one
-/// address unit wide.  For example, on a machine which has 16 bit bytes returns
-/// an i16*.
-extern Type *GetUnitPointerType(LLVMContext &C, unsigned AddrSpace = 0);
-
-/// GetFieldIndex - Return the index of the field in the given LLVM type that
-/// corresponds to the GCC field declaration 'decl'.  This means that the LLVM
-/// and GCC fields start in the same byte (if 'decl' is a bitfield, this means
-/// that its first bit is within the byte the LLVM field starts at).  Returns
-/// INT_MAX if there is no such LLVM field.
-int GetFieldIndex(tree_node *decl, Type *Ty);
-
 /// isPassedByInvisibleReference - Return true if the specified type should be
 /// passed by 'invisible reference'. In other words, instead of passing the
 /// thing by value, pass the address of a temporary.
 bool isPassedByInvisibleReference(tree_node *type);
 
-/// isSequentialCompatible - Return true if the specified gcc array, pointer or
-/// vector type and the corresponding LLVM SequentialType lay out their elements
-/// identically in memory, so doing a GEP accesses the right memory location.
-/// We assume that objects without a known size do not.
-extern bool isSequentialCompatible(tree_node *type);
-
 /// OffsetIsLLVMCompatible - Return true if the given field is offset from the
 /// start of the record by a constant amount which is not humongously big.
 extern bool OffsetIsLLVMCompatible(tree_node *field_decl);
 
-#define NO_LENGTH (~(uint64_t)0)
-
-/// ArrayLengthOf - Returns the length of the given gcc array type, or NO_LENGTH
-/// if the array has variable or unknown length.
-extern uint64_t ArrayLengthOf(tree_node *type);
-
 /// isBitfield - Returns whether to treat the specified field as a bitfield.
 bool isBitfield(tree_node *field_decl);
 

Added: dragonegg/trunk/include/dragonegg/Types.h
URL: http://llvm.org/viewvc/llvm-project/dragonegg/trunk/include/dragonegg/Types.h?rev=136966&view=auto
==============================================================================
--- dragonegg/trunk/include/dragonegg/Types.h (added)
+++ dragonegg/trunk/include/dragonegg/Types.h Fri Aug  5 04:59:30 2011
@@ -0,0 +1,99 @@
+//=---------- Types.h - Converting and working with types ---------*- C++ -*-=//
+//
+// Copyright (C) 2011  Duncan Sands.
+//
+// This file is part of DragonEgg.
+//
+// DragonEgg is free software; you can redistribute it and/or modify it under
+// the terms of the GNU General Public License as published by the Free Software
+// Foundation; either version 2, or (at your option) any later version.
+//
+// DragonEgg 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
+// DragonEgg; see the file COPYING.  If not, write to the Free Software
+// Foundation, 51 Franklin Street, Suite 500, Boston, MA 02110-1335, USA.
+//
+//===----------------------------------------------------------------------===//
+// This file declares functions for converting GCC types to LLVM types, and for
+// working with types.
+//===----------------------------------------------------------------------===//
+
+#ifndef DRAGONEGG_TYPES_H
+#define DRAGONEGG_TYPES_H
+
+// LLVM headers
+#include "llvm/CallingConv.h"
+
+// Forward declarations.
+namespace llvm {
+  class AttrListPtr;
+  class FunctionType;
+  class LLVMContext;
+  class Type;
+}
+union tree_node;
+
+/// GetUnitType - Returns an integer one address unit wide if 'NumUnits' is 1;
+/// otherwise returns an array of such integers with 'NumUnits' elements.  For
+/// example, on a machine which has 16 bit bytes returns an i16 or an array of
+/// i16.
+extern llvm::Type *GetUnitType(llvm::LLVMContext &C, unsigned NumUnits = 1);
+
+/// GetUnitPointerType - Returns an LLVM pointer type which points to memory one
+/// address unit wide.  For example, on a machine which has 16 bit bytes returns
+/// an i16*.
+extern llvm::Type *GetUnitPointerType(llvm::LLVMContext &C,
+                                      unsigned AddrSpace = 0);
+
+/// getRegType - Returns the LLVM type to use for registers that hold a value
+/// of the scalar GCC type 'type'.  All of the EmitReg* routines use this to
+/// determine the LLVM type to return.
+extern llvm::Type *getRegType(tree_node *type);
+
+/// getPointerToType - Returns the LLVM register type to use for a pointer to
+/// the given GCC type.
+extern llvm::Type *getPointerToType(tree_node *type);
+
+/// ConvertType - Returns the LLVM type to use for memory that holds a value
+/// of the given GCC type (getRegType should be used for values in registers).
+extern llvm::Type *ConvertType(tree_node *type);
+
+/// ConvertFunctionType - Convert the specified FUNCTION_TYPE or METHOD_TYPE
+/// tree to an LLVM type.  This does the same thing that ConvertType does, but
+/// it also returns the function's LLVM calling convention and attributes.
+extern llvm::FunctionType *ConvertFunctionType(tree_node *type, tree_node *decl,
+                                               tree_node *static_chain,
+                                               llvm::CallingConv::ID &CC,
+                                               llvm::AttrListPtr &PAL);
+
+/// ConvertArgListToFnType - Given a DECL_ARGUMENTS list on an GCC tree,
+/// return the LLVM type corresponding to the function.  This is useful for
+/// turning "T foo(...)" functions into "T foo(void)" functions.
+llvm::FunctionType *ConvertArgListToFnType(tree_node *type, tree_node *arglist,
+                                           tree_node *static_chain,
+                                           llvm::CallingConv::ID &CC,
+                                           llvm::AttrListPtr &PAL);
+
+/// GetFieldIndex - Return the index of the field in the given LLVM type that
+/// corresponds to the GCC field declaration 'decl'.  This means that the LLVM
+/// and GCC fields start in the same byte (if 'decl' is a bitfield, this means
+/// that its first bit is within the byte the LLVM field starts at).  Returns
+/// INT_MAX if there is no such LLVM field.
+int GetFieldIndex(tree_node *decl, llvm::Type *Ty);
+
+/// isSequentialCompatible - Return true if the specified gcc array, pointer or
+/// vector type and the corresponding LLVM SequentialType lay out their elements
+/// identically in memory, so doing a GEP accesses the right memory location.
+/// We assume that objects without a known size do not.
+extern bool isSequentialCompatible(tree_node *type);
+
+#define NO_LENGTH (~(uint64_t)0)
+
+/// ArrayLengthOf - Returns the length of the given gcc array type, or NO_LENGTH
+/// if the array has variable or unknown length.
+extern uint64_t ArrayLengthOf(tree_node *type);
+
+#endif /* DRAGONEGG_TYPES_H */

Modified: dragonegg/trunk/src/Backend.cpp
URL: http://llvm.org/viewvc/llvm-project/dragonegg/trunk/src/Backend.cpp?rev=136966&r1=136965&r2=136966&view=diff
==============================================================================
--- dragonegg/trunk/src/Backend.cpp (original)
+++ dragonegg/trunk/src/Backend.cpp Fri Aug  5 04:59:30 2011
@@ -30,6 +30,7 @@
 #include "dragonegg/OS.h"
 #include "dragonegg/Target.h"
 #include "dragonegg/Trees.h"
+#include "dragonegg/Types.h"
 
 // LLVM headers
 #define DEBUG_TYPE "plugin"
@@ -100,7 +101,6 @@
 PassManagerBuilder PassBuilder;
 TargetMachine *TheTarget = 0;
 TargetFolder *TheFolder = 0;
-TypeConverter *TheTypeConverter = 0;
 raw_ostream *OutStream = 0; // Stream to write assembly code to.
 formatted_raw_ostream FormattedOutStream;
 
@@ -533,7 +533,6 @@
   // Create a module to hold the generated LLVM IR.
   CreateModule(TargetTriple);
 
-  TheTypeConverter = new TypeConverter();
   TheFolder = new TargetFolder(TheTarget->getTargetData());
 
   if (debug_info_level > DINFO_LEVEL_NONE)
@@ -1092,9 +1091,8 @@
     if (FnEntry == 0) {
       CallingConv::ID CC;
       AttrListPtr PAL;
-      FunctionType *Ty =
-        TheTypeConverter->ConvertFunctionType(TREE_TYPE(decl), decl, NULL,
-                                              CC, PAL);
+      FunctionType *Ty = ConvertFunctionType(TREE_TYPE(decl), decl, NULL, CC,
+                                             PAL);
       FnEntry = Function::Create(Ty, Function::ExternalLinkage, Name, TheModule);
       FnEntry->setCallingConv(CC);
       FnEntry->setAttributes(PAL);

Modified: dragonegg/trunk/src/Constants.cpp
URL: http://llvm.org/viewvc/llvm-project/dragonegg/trunk/src/Constants.cpp?rev=136966&r1=136965&r2=136966&view=diff
==============================================================================
--- dragonegg/trunk/src/Constants.cpp (original)
+++ dragonegg/trunk/src/Constants.cpp Fri Aug  5 04:59:30 2011
@@ -22,8 +22,8 @@
 
 // Plugin headers
 #include "dragonegg/Constants.h"
-#include "dragonegg/Internals.h"
 #include "dragonegg/Trees.h"
+#include "dragonegg/Types.h"
 #include "dragonegg/ADT/IntervalList.h"
 #include "dragonegg/ADT/Range.h"
 extern "C" {
@@ -54,6 +54,8 @@
 #include "tm_p.h"
 }
 
+using namespace llvm;
+
 static LLVMContext &Context = getGlobalContext();
 
 // Forward declarations.

Modified: dragonegg/trunk/src/Convert.cpp
URL: http://llvm.org/viewvc/llvm-project/dragonegg/trunk/src/Convert.cpp?rev=136966&r1=136965&r2=136966&view=diff
==============================================================================
--- dragonegg/trunk/src/Convert.cpp (original)
+++ dragonegg/trunk/src/Convert.cpp Fri Aug  5 04:59:30 2011
@@ -26,6 +26,7 @@
 #include "dragonegg/Constants.h"
 #include "dragonegg/Debug.h"
 #include "dragonegg/Trees.h"
+#include "dragonegg/Types.h"
 
 // LLVM headers
 #include "llvm/Module.h"
@@ -518,16 +519,12 @@
   }
 
   if (getFunctionTypeFromArgList)
-    FTy = TheTypeConverter->ConvertArgListToFnType(TREE_TYPE(FnDecl),
-                                                   DECL_ARGUMENTS(FnDecl),
-                                                   static_chain,
-                                                   CallingConv, PAL);
+    FTy = ConvertArgListToFnType(TREE_TYPE(FnDecl), DECL_ARGUMENTS(FnDecl),
+                                 static_chain, CallingConv, PAL);
   else
     // Otherwise, just get the type from the function itself.
-    FTy = TheTypeConverter->ConvertFunctionType(TREE_TYPE(FnDecl),
-                                                FnDecl,
-                                                static_chain,
-                                                CallingConv, PAL);
+    FTy = ConvertFunctionType(TREE_TYPE(FnDecl), FnDecl, static_chain,
+                              CallingConv, PAL);
 
   // If we've already seen this function and created a prototype, and if the
   // proto has the right LLVM type, just use it.
@@ -8539,11 +8536,8 @@
   CallingConv::ID CallingConv;
   AttrListPtr PAL;
 
-  Type *Ty =
-    TheTypeConverter->ConvertFunctionType(function_type,
-                                          fndecl,
-                                          gimple_call_chain(stmt),
-                                          CallingConv, PAL);
+  Type *Ty = ConvertFunctionType(function_type, fndecl, gimple_call_chain(stmt),
+                                 CallingConv, PAL);
 
   // If this is a direct call to a function using a static chain then we need
   // to ensure the function type is the one just calculated: it has an extra

Modified: dragonegg/trunk/src/Types.cpp
URL: http://llvm.org/viewvc/llvm-project/dragonegg/trunk/src/Types.cpp?rev=136966&r1=136965&r2=136966&view=diff
==============================================================================
--- dragonegg/trunk/src/Types.cpp (original)
+++ dragonegg/trunk/src/Types.cpp Fri Aug  5 04:59:30 2011
@@ -24,6 +24,7 @@
 // Plugin headers
 #include "dragonegg/ABI.h"
 #include "dragonegg/Trees.h"
+#include "dragonegg/Types.h"
 extern "C" {
 #include "dragonegg/cache.h"
 }
@@ -54,6 +55,9 @@
 
 static LLVMContext &Context = getGlobalContext();
 
+/// SCCInProgress - Set of mutually dependent types currently being converted.
+static const std::vector<tree_node*> *SCCInProgress;
+
 /// ContainedTypeIterator - A convenience class for viewing a type as a graph,
 /// where the nodes of the graph are types and there is an edge from type A to
 /// type B iff A "contains" B.  A record type contains the types of its fields,
@@ -476,635 +480,285 @@
   return ConvertType(type)->getPointerTo();
 }
 
-/// mayRecurse - Return true if converting this type may require breaking a
-/// self-referential type loop.  For example, converting the struct type
-///   struct S;
-///   struct S {
-///     struct S* s;
-///   };
-/// requires converting the "struct S*" field type; converting that pointer
-/// type requires converting "struct S", leading to an infinite loop.  On the
-/// other hand simple types like integers are never self-referential.  As this
-/// routine is intended to be quick and simple, it returns true when in doubt.
-/// Note that if a complicated type has already been converted then false is
-/// usually returned, since type conversion doesn't have to do anything except
-/// return the previously computed LLVM type.  The exception is record or union
-/// types which were first converted when incomplete but that are now complete
-/// so need to be converted again.
-static bool mayRecurse(tree type) {
-  assert(type == TYPE_MAIN_VARIANT(type) && "Not converting the main variant!");
-  switch (TREE_CODE(type)) {
-  default:
-    assert(false && "Unknown type!");
-
-  case BOOLEAN_TYPE:
-  case ENUMERAL_TYPE:
-  case FIXED_POINT_TYPE:
-  case INTEGER_TYPE:
-  case OFFSET_TYPE:
-  case REAL_TYPE:
-  case VOID_TYPE:
-    // Simple types that are never self-referential.
-    return false;
-
-  case COMPLEX_TYPE:
-  case VECTOR_TYPE:
-    // Converting these types does involve converting another type, however that
-    // conversion cannot refer back to the initial type.
-    // NOTE: GCC supports vectors of pointers, and the pointer could refer back
-    // to the vector.  However as LLVM does not support vectors of pointers we
-    // don't convert the pointer type and just use an integer instead, so as far
-    // as we are concerned such vector types are not self-referential.
-    return false;
-
-  case ARRAY_TYPE:
-  case FUNCTION_TYPE:
-  case METHOD_TYPE:
-  case POINTER_TYPE:
-  case REFERENCE_TYPE:
-    // Converting these types may recurse unless the type was already converted.
-    return !llvm_has_type(type);
-
-  case QUAL_UNION_TYPE:
-  case RECORD_TYPE:
-  case UNION_TYPE: {
-    // Converting these types may recurse unless already converted.  However if
-    // the type was converted when still incomplete but is now complete then it
-    // needs to be converted again, which might recurse.
 
-    // If the type is incomplete then converting it will not recurse (conversion
-    // just returns an opaque type).
-    if (!TYPE_SIZE(type))
-      return false;
-
-    // If the type was not previously converted then converting it may recurse.
-    Type *Ty = GET_TYPE_LLVM(type);
-    if (!Ty)
-      return true;
+//===----------------------------------------------------------------------===//
+//                  FUNCTION/METHOD_TYPE Conversion Routines
+//===----------------------------------------------------------------------===//
 
-    // If the type was previously converted when incomplete then converting it
-    // may recurse as the type is now complete so needs to be converted again.
-    if (cast<StructType>(Ty)->isOpaque())
-      return true;
+namespace {
+  class FunctionTypeConversion : public DefaultABIClient {
+    Type *&RetTy;
+    SmallVectorImpl<Type*> &ArgTypes;
+    CallingConv::ID &CallingConv;
+    bool isShadowRet;
+    bool KNRPromotion;
+    unsigned Offset;
+  public:
+    FunctionTypeConversion(Type *&retty, SmallVectorImpl<Type*> &AT,
+                           CallingConv::ID &CC, bool KNR)
+      : RetTy(retty), ArgTypes(AT), CallingConv(CC), KNRPromotion(KNR),
+        Offset(0) {
+      CallingConv = CallingConv::C;
+      isShadowRet = false;
+    }
 
-    // The type was already converted and does not need to be converted again.
-    return false;
-  }
-  }
-}
+    /// getCallingConv - This provides the desired CallingConv for the function.
+    CallingConv::ID getCallingConv(void) { return CallingConv; }
 
-/// RecursiveTypeIterator - A convenience class that visits only those nodes
-/// in the type graph that mayRecurse thinks might be self-referential.  Note
-/// that dereferencing returns the main variant of the contained type rather
-/// than the contained type itself.  See ContainedTypeIterator and mayRecurse
-/// for more information about the type graph and self-referential types.
-namespace {
+    bool isShadowReturn() const { return isShadowRet; }
 
-  class RecursiveTypeIterator {
-    // This class wraps an iterator that visits all contained types, and just
-    // increments the iterator over any contained types that will not recurse.
-    ContainedTypeIterator I;
+    /// HandleScalarResult - This callback is invoked if the function returns a
+    /// simple scalar result value.
+    void HandleScalarResult(Type *RetTy) {
+      this->RetTy = RetTy;
+    }
 
-    /// SkipNonRecursiveTypes - Increment the wrapped iterator over any types
-    /// that mayRecurse says can be converted directly without having to worry
-    /// about self-recursion.
-    void SkipNonRecursiveTypes() {
-      while (I != ContainedTypeIterator::end() &&
-             !mayRecurse(TYPE_MAIN_VARIANT(*I)))
-        ++I;
+    /// HandleAggregateResultAsScalar - This callback is invoked if the function
+    /// returns an aggregate value by bit converting it to the specified scalar
+    /// type and returning that.
+    void HandleAggregateResultAsScalar(Type *ScalarTy, unsigned Offset=0) {
+      RetTy = ScalarTy;
+      this->Offset = Offset;
     }
 
-    /// RecursiveTypeIterator - Convenience constructor for internal use.
-    explicit RecursiveTypeIterator(const ContainedTypeIterator& i) : I(i) {}
+    /// HandleAggregateResultAsAggregate - This callback is invoked if the function
+    /// returns an aggregate value using multiple return values.
+    void HandleAggregateResultAsAggregate(Type *AggrTy) {
+      RetTy = AggrTy;
+    }
 
-  public:
+    /// HandleShadowResult - Handle an aggregate or scalar shadow argument.
+    void HandleShadowResult(PointerType *PtrArgTy, bool RetPtr) {
+      // This function either returns void or the shadow argument,
+      // depending on the target.
+      RetTy = RetPtr ? PtrArgTy : Type::getVoidTy(Context);
 
-    /// Dereference operator returning the main variant of the contained type.
-    tree operator*() {
-      return TYPE_MAIN_VARIANT(*I);
-    };
+      // In any case, there is a dummy shadow argument though!
+      ArgTypes.push_back(PtrArgTy);
 
-    /// Comparison operators.
-    bool operator==(const RecursiveTypeIterator &other) const {
-      return other.I == this->I;
-    }
-    bool operator!=(const RecursiveTypeIterator &other) const {
-      return !(*this == other);
+      // Also, note the use of a shadow argument.
+      isShadowRet = true;
     }
 
-    /// Postfix increment operator.
-    RecursiveTypeIterator operator++(int) {
-      RecursiveTypeIterator Result(*this);
-      ++(*this);
-      return Result;
+    /// HandleAggregateShadowResult - This callback is invoked if the function
+    /// returns an aggregate value by using a "shadow" first parameter, which is
+    /// a pointer to the aggregate, of type PtrArgTy.  If RetPtr is set to true,
+    /// the pointer argument itself is returned from the function.
+    void HandleAggregateShadowResult(PointerType *PtrArgTy,
+                                       bool RetPtr) {
+      HandleShadowResult(PtrArgTy, RetPtr);
     }
 
-    /// Prefix increment operator.
-    RecursiveTypeIterator& operator++() {
-      ++I;
-      SkipNonRecursiveTypes();
-      return *this;
+    /// HandleScalarShadowResult - This callback is invoked if the function
+    /// returns a scalar value by using a "shadow" first parameter, which is a
+    /// pointer to the scalar, of type PtrArgTy.  If RetPtr is set to true,
+    /// the pointer argument itself is returned from the function.
+    void HandleScalarShadowResult(PointerType *PtrArgTy, bool RetPtr) {
+      HandleShadowResult(PtrArgTy, RetPtr);
     }
 
-    /// begin - Return an iterator referring to the first type contained in the
-    /// given type.
-    static RecursiveTypeIterator begin(tree type) {
-      RecursiveTypeIterator R(ContainedTypeIterator::begin(type));
-      R.SkipNonRecursiveTypes();
-      return R;
+    void HandlePad(llvm::Type *LLVMTy) {
+      HandleScalarArgument(LLVMTy, 0, 0);
     }
 
-    /// end - Return the end iterator for contained type iteration.
-    static RecursiveTypeIterator end() {
-      return RecursiveTypeIterator(ContainedTypeIterator::end());
+    void HandleScalarArgument(llvm::Type *LLVMTy, tree type,
+                              unsigned /*RealSize*/ = 0) {
+      if (KNRPromotion) {
+        if (type == float_type_node)
+          LLVMTy = ConvertType(double_type_node);
+        else if (LLVMTy->isIntegerTy(16) || LLVMTy->isIntegerTy(8) ||
+                 LLVMTy->isIntegerTy(1))
+          LLVMTy = Type::getInt32Ty(Context);
+      }
+      ArgTypes.push_back(LLVMTy);
     }
-  };
 
-} // Unnamed namespace.
-
-// Traits for working with the graph of possibly self-referential type nodes,
-// see RecursiveTypeIterator.
-namespace llvm {
-  template <> struct GraphTraits<tree> {
-    typedef tree_node NodeType;
-    typedef RecursiveTypeIterator ChildIteratorType;
-    static inline NodeType *getEntryNode(tree t) {
-      assert(TYPE_P(t) && "Expected a type!");
-      return t;
+    /// HandleByInvisibleReferenceArgument - This callback is invoked if a pointer
+    /// (of type PtrTy) to the argument is passed rather than the argument itself.
+    void HandleByInvisibleReferenceArgument(llvm::Type *PtrTy,
+                                            tree /*type*/) {
+      ArgTypes.push_back(PtrTy);
     }
-    static inline ChildIteratorType child_begin(tree type) {
-      return ChildIteratorType::begin(type);
+
+    /// HandleByValArgument - This callback is invoked if the aggregate function
+    /// argument is passed by value. It is lowered to a parameter passed by
+    /// reference with an additional parameter attribute "ByVal".
+    void HandleByValArgument(llvm::Type *LLVMTy, tree type) {
+      HandleScalarArgument(LLVMTy->getPointerTo(), type);
     }
-    static inline ChildIteratorType child_end(tree) {
-      return ChildIteratorType::end();
+
+    /// HandleFCAArgument - This callback is invoked if the aggregate function
+    /// argument is a first class aggregate passed by value.
+    void HandleFCAArgument(llvm::Type *LLVMTy, tree /*type*/) {
+      ArgTypes.push_back(LLVMTy);
     }
   };
 }
 
-/// ConvertNonRecursiveType - Convert a type when this is known to not require
-/// breaking type conversion loops, see mayRecurse.
-static Type *ConvertNonRecursiveType(tree type) {
-  assert(type == TYPE_MAIN_VARIANT(type) && "Not converting the main variant!");
-  assert(!mayRecurse(type) && "Expected a non-recursive type!");
-
-  switch (TREE_CODE(type)) {
-  default:
-    DieAbjectly("Unknown or recursive type!", type);
 
-  case ARRAY_TYPE:
-  case FUNCTION_TYPE:
-  case METHOD_TYPE:
-  case POINTER_TYPE:
-  case REFERENCE_TYPE: {
-    // If these types are not recursive it can only be because they were already
-    // converted and we can safely return the result of the previous conversion.
-    Type *Ty = GET_TYPE_LLVM(type);
-    assert(Ty && "Type not already converted!");
-    return Ty;
+static Attributes HandleArgumentExtension(tree ArgTy) {
+  if (TREE_CODE(ArgTy) == BOOLEAN_TYPE) {
+    if (TREE_INT_CST_LOW(TYPE_SIZE(ArgTy)) < INT_TYPE_SIZE)
+      return Attribute::ZExt;
+  } else if (TREE_CODE(ArgTy) == INTEGER_TYPE &&
+             TREE_INT_CST_LOW(TYPE_SIZE(ArgTy)) < INT_TYPE_SIZE) {
+    if (TYPE_UNSIGNED(ArgTy))
+      return Attribute::ZExt;
+    else
+      return Attribute::SExt;
   }
 
-  case ENUMERAL_TYPE:
-    // If the enum is incomplete return a placeholder type.
-    if (!TYPE_SIZE(type))
-      return Type::getInt32Ty(Context);
-    // Otherwise fall through.
-  case BOOLEAN_TYPE:
-  case INTEGER_TYPE: {
-    uint64_t Size = getInt64(TYPE_SIZE(type), true);
-    return IntegerType::get(Context, Size); // Not worth caching.
-  }
+  return Attribute::None;
+}
 
-  case COMPLEX_TYPE: {
-    if (Type *Ty = GET_TYPE_LLVM(type)) return Ty;
-    Type *Ty = ConvertNonRecursiveType(TYPE_MAIN_VARIANT(TREE_TYPE(type)));
-    Ty = StructType::get(Ty, Ty, NULL);
-    return SET_TYPE_LLVM(type, Ty);
-  }
+/// ConvertParamListToLLVMSignature - This method is used to build the argument
+/// type list for K&R prototyped functions.  In this case, we have to figure out
+/// the type list (to build a FunctionType) from the actual DECL_ARGUMENTS list
+/// for the function.  This method takes the DECL_ARGUMENTS list (Args), and
+/// fills in Result with the argument types for the function.  It returns the
+/// specified result type for the function.
+FunctionType *ConvertArgListToFnType(tree type, tree Args, tree static_chain,
+                                     CallingConv::ID &CallingConv,
+                                     AttrListPtr &PAL) {
+  tree ReturnType = TREE_TYPE(type);
+  SmallVector<Type*, 8> ArgTys;
+  Type *RetTy(Type::getVoidTy(Context));
 
-  case OFFSET_TYPE:
-    // Handle OFFSET_TYPE specially.  This is used for pointers to members,
-    // which are really just integer offsets.  Return the appropriate integer
-    // type directly.
-    return getTargetData().getIntPtrType(Context); // Not worth caching.
+  FunctionTypeConversion Client(RetTy, ArgTys, CallingConv, true /*K&R*/);
+  DefaultABI ABIConverter(Client);
 
-  case REAL_TYPE:
-    // It is not worth caching the result of this type conversion.
-    switch (TYPE_PRECISION(type)) {
-    default:
-      DieAbjectly("Unknown FP type!", type);
-    case 32: return Type::getFloatTy(Context);
-    case 64: return Type::getDoubleTy(Context);
-    case 80: return Type::getX86_FP80Ty(Context);
-    case 128:
-#ifdef TARGET_POWERPC
-      return Type::getPPC_FP128Ty(Context);
-#else
-      // IEEE quad precision.
-      return Type::getFP128Ty(Context);
+#ifdef TARGET_ADJUST_LLVM_CC
+  TARGET_ADJUST_LLVM_CC(CallingConv, type);
 #endif
-    }
-
-  case RECORD_TYPE:
-  case QUAL_UNION_TYPE:
-  case UNION_TYPE:
-    // If the type was already converted then return the already computed type.
-    if (Type *Ty = GET_TYPE_LLVM(type)) return Ty;
-
-    // Otherwise this must be an incomplete type - return an opaque struct.
-    assert(!TYPE_SIZE(type) && "Expected an incomplete type!");
-    return SET_TYPE_LLVM(type, StructType::createNamed(Context,
-                                                     getDescriptiveName(type)));
 
-  case VECTOR_TYPE: {
-    if (Type *Ty = GET_TYPE_LLVM(type)) return Ty;
-    Type *Ty;
-    // LLVM does not support vectors of pointers, so turn any pointers into
-    // integers.
-    if (POINTER_TYPE_P(TREE_TYPE(type)))
-      Ty = getTargetData().getIntPtrType(Context);
-    else
-      Ty = ConvertNonRecursiveType(TYPE_MAIN_VARIANT(TREE_TYPE(type)));
-    Ty = VectorType::get(Ty, TYPE_VECTOR_SUBPARTS(type));
-    return SET_TYPE_LLVM(type, Ty);
-  }
+  // Builtins are always prototyped, so this isn't one.
+  ABIConverter.HandleReturnType(ReturnType, current_function_decl, false);
 
-  case VOID_TYPE:
-    return Type::getVoidTy(Context); // Not worth caching.
-  }
-}
+  SmallVector<AttributeWithIndex, 8> Attrs;
 
-/// ConvertRecursiveType - Convert a type when conversion may require breaking
-/// type conversion loops, see mayRecurse.  Note that all types used by but not
-/// in the current strongly connected component (SCC) must have been converted
-/// already.
-Type *TypeConverter::ConvertRecursiveType(tree type) {
-  assert(type == TYPE_MAIN_VARIANT(type) && "Not converting the main variant!");
-  assert(mayRecurse(type) && "Expected a recursive type!");
-  assert(SCCInProgress && "Missing recursion data!");
+  // Compute whether the result needs to be zext or sext'd.
+  Attributes RAttributes = HandleArgumentExtension(ReturnType);
 
-#ifndef NDEBUG
-  // Check that the given type is in the current strongly connected component
-  // (SCC) of the type graph.  This should always be the case because SCCs are
-  // visited bottom up.
-  bool inSCC = false;
-  for (unsigned i = 0, e = SCCInProgress->size(); i != e; ++i)
-    if ((*SCCInProgress)[i] == type) {
-      inSCC = true;
-      break;
-    }
-  if (!inSCC)
-    DieAbjectly("Type not in SCC!", type);
+  // Allow the target to change the attributes.
+#ifdef TARGET_ADJUST_LLVM_RETATTR
+  TARGET_ADJUST_LLVM_RETATTR(RAttributes, type);
 #endif
 
-  switch (TREE_CODE(type)) {
-  default:
-    DieAbjectly("Unexpected type!", type);
-
-  case QUAL_UNION_TYPE:
-  case RECORD_TYPE:
-  case UNION_TYPE:
-    return SET_TYPE_LLVM(type, ConvertRECORD(type));
+  if (RAttributes != Attribute::None)
+    Attrs.push_back(AttributeWithIndex::get(0, RAttributes));
 
-  case POINTER_TYPE:
-  case REFERENCE_TYPE: {
-    // This is where self-recursion loops are broken, by not converting the type
-    // pointed to if this would cause trouble (the pointer type is turned into
-    // {}* instead).
-    tree pointee = TYPE_MAIN_VARIANT(TREE_TYPE(type));
+  // If this function returns via a shadow argument, the dest loc is passed
+  // in as a pointer.  Mark that pointer as struct-ret and noalias.
+  if (ABIConverter.isShadowReturn())
+    Attrs.push_back(AttributeWithIndex::get(ArgTys.size(),
+                                    Attribute::StructRet | Attribute::NoAlias));
 
-    // The pointer type is in the strongly connected component (SCC) currently
-    // being converted.  Check whether the pointee is as well.  If there is more
-    // than one type in the SCC then necessarily the pointee type is in the SCC
-    // since any path from the pointer type to the other type necessarily passes
-    // via the pointee.  If the pointer type is the only element of the SCC then
-    // the pointee is only in the SCC if it is equal to the pointer.
-    bool bothInSCC = SCCInProgress->size() != 1 || pointee == type;
+  std::vector<Type*> ScalarArgs;
+  if (static_chain) {
+    // Pass the static chain as the first parameter.
+    ABIConverter.HandleArgument(TREE_TYPE(static_chain), ScalarArgs);
+    // Mark it as the chain argument.
+    Attrs.push_back(AttributeWithIndex::get(ArgTys.size(),
+                                             Attribute::Nest));
+  }
 
-    Type *PointeeTy;
-    if (!bothInSCC) {
-      // It is safe to convert the pointee.  This is the common case, as we get
-      // here for pointers to integers and so on.
-      PointeeTy = ConvertType(pointee);
-      if (PointeeTy->isVoidTy())
-        PointeeTy = GetUnitType(Context); // void* -> byte*.
-    } else {
-      // Both the pointer and the pointee type are in the SCC so it is not safe
-      // to convert the pointee type - otherwise we would get an infinite loop.
-      // However if a type, for example an opaque struct placeholder, has been
-      // registered for the pointee then we can return a pointer to it, giving
-      // nicer IR (this is not needed for correctness).  Note that some members
-      // of the SCC may have been converted already at this point (for this to
-      // happen there must be more than one pointer type in the SCC), and thus
-      // will have LLVM types registered for them.  Unfortunately which types
-      // have been converted depends on the order in which we visit the SCC, and
-      // that is not an intrinsic property of the SCC.  This is why we choose to
-      // only use the types registered for records and unions - these are always
-      // available.  As a further attempt to improve the IR, we return an S* for
-      // an array type S[N] if (recursively) S is a record or union type.
+  for (; Args && TREE_TYPE(Args) != void_type_node; Args = TREE_CHAIN(Args)) {
+    tree ArgTy = TREE_TYPE(Args);
 
-      // Drill down through nested arrays to the ultimate element type.  Thanks
-      // to this we may return S* for a (S[])*, which is better than {}*.
-      while (TREE_CODE(pointee) == ARRAY_TYPE)
-        pointee = TYPE_MAIN_VARIANT(TREE_TYPE(pointee));
+    // Determine if there are any attributes for this param.
+    Attributes PAttributes = Attribute::None;
 
-      // If the pointee is a record or union type then return a pointer to its
-      // placeholder type.  Otherwise return {}*.
-      if (TREE_CODE(pointee) == QUAL_UNION_TYPE ||
-          TREE_CODE(pointee) == RECORD_TYPE ||
-          TREE_CODE(pointee) == UNION_TYPE)
-        PointeeTy = GET_TYPE_LLVM(pointee);
-      else
-        PointeeTy = StructType::get(Context);
-    }
+    ABIConverter.HandleArgument(ArgTy, ScalarArgs, &PAttributes);
 
-    return SET_TYPE_LLVM(type, PointeeTy->getPointerTo());
-  }
+    // Compute zext/sext attributes.
+    PAttributes |= HandleArgumentExtension(ArgTy);
 
-  case METHOD_TYPE:
-  case FUNCTION_TYPE: {
-    CallingConv::ID CallingConv;
-    AttrListPtr PAL;
-    // No declaration to pass through, passing NULL.
-    return SET_TYPE_LLVM(type, ConvertFunctionType(type, NULL, NULL,
-                                                   CallingConv, PAL));
+    if (PAttributes != Attribute::None)
+      Attrs.push_back(AttributeWithIndex::get(ArgTys.size(), PAttributes));
   }
 
-  case ARRAY_TYPE: {
-    Type *ElementTy = ConvertType(TREE_TYPE(type));
-    uint64_t NumElements = ArrayLengthOf(type);
-
-    if (NumElements == NO_LENGTH) // Variable length array?
-      NumElements = 0;
+  PAL = AttrListPtr::get(Attrs.begin(), Attrs.end());
+  return FunctionType::get(RetTy, ArgTys, false);
+}
 
-    // Create the array type.
-    Type *Ty = ArrayType::get(ElementTy, NumElements);
+FunctionType *ConvertFunctionType(tree type, tree decl, tree static_chain,
+                                  CallingConv::ID &CallingConv,
+                                  AttrListPtr &PAL) {
+  Type *RetTy = Type::getVoidTy(Context);
+  SmallVector<Type*, 8> ArgTypes;
+  bool isVarArg = false;
+  FunctionTypeConversion Client(RetTy, ArgTypes, CallingConv, false/*not K&R*/);
+  DefaultABI ABIConverter(Client);
 
-    // If the user increased the alignment of the array element type, then the
-    // size of the array is rounded up by that alignment even though the size
-    // of the array element type is not (!).  Correct for this if necessary by
-    // adding padding.  May also need padding if the element type has variable
-    // size and the array type has variable length, but by a miracle the product
-    // gives a constant size.
-    if (isInt64(TYPE_SIZE(type), true)) {
-      uint64_t PadBits = getInt64(TYPE_SIZE(type), true) -
-        getTargetData().getTypeAllocSizeInBits(Ty);
-      if (PadBits) {
-        Type *Padding = ArrayType::get(Type::getInt8Ty(Context), PadBits / 8);
-        Ty = StructType::get(Ty, Padding, NULL);
-      }
-    }
+  // Allow the target to set the CC for things like fastcall etc.
+#ifdef TARGET_ADJUST_LLVM_CC
+  TARGET_ADJUST_LLVM_CC(CallingConv, type);
+#endif
 
-    return SET_TYPE_LLVM(type, Ty);
-  }
-  }
-}
+  ABIConverter.HandleReturnType(TREE_TYPE(type), current_function_decl,
+                                decl ? DECL_BUILT_IN(decl) : false);
 
-Type *TypeConverter::ConvertType(tree type) {
-  if (type == error_mark_node) return Type::getInt32Ty(Context);
+  // Compute attributes for return type (and function attributes).
+  SmallVector<AttributeWithIndex, 8> Attrs;
+  Attributes FnAttributes = Attribute::None;
 
-  // LLVM doesn't care about variants such as const, volatile, or restrict.
-  type = TYPE_MAIN_VARIANT(type);
+  int flags = flags_from_decl_or_type(decl ? decl : type);
 
-  // If this type can be converted without special action being needed to avoid
-  // conversion loops coming from self-referential types, then convert it.
-  if (!mayRecurse(type))
-    return ConvertNonRecursiveType(type);
+  // Check for 'noreturn' function attribute.
+  if (flags & ECF_NORETURN)
+    FnAttributes |= Attribute::NoReturn;
 
-  // If we already started a possibly looping type conversion, continue with it.
-  if (SCCInProgress)
-    return ConvertRecursiveType(type);
+  // Check for 'nounwind' function attribute.
+  if (flags & ECF_NOTHROW)
+    FnAttributes |= Attribute::NoUnwind;
 
-  // Begin converting a type for which the conversion may require breaking type
-  // conversion loops coming from self-referential types, see mayRecurse.  First
-  // analyse all of the types that will need to be converted in order to convert
-  // this one, finding sets of types that must be converted simultaneously (i.e.
-  // for which converting any one of them requires converting all of the others;
-  // these sets are the strongly connected components (SCCs) of the type graph),
-  // then visit them bottom up, converting all types in them.  "Bottom up" means
-  // that if a type in a SCC makes use of a type T that is not in the SCC then T
-  // will be visited first.  Note that this analysis is performed only once: the
-  // results of the type conversion are cached, and any future conversion of one
-  // of the visited types will just return the cached value.
-  for (scc_iterator<tree> I = scc_begin(type), E = scc_end(type); I != E; ++I) {
-    const std::vector<tree> &SCC = *I;
-
-    // First create a placeholder opaque struct for every record or union type
-    // in the SCC.  This way, if we have both "struct S" and "struct S*" in the
-    // SCC then we can return an LLVM "%struct.s*" for the pointer rather than
-    // the nasty {}* type we are obliged to return in general.
-    for (unsigned i = 0, e = SCC.size(); i != e; ++i) {
-      tree some_type = SCC[i];
-      if (TREE_CODE(some_type) != QUAL_UNION_TYPE &&
-          TREE_CODE(some_type) != RECORD_TYPE &&
-          TREE_CODE(some_type) != UNION_TYPE) {
-        assert(!llvm_has_type(some_type) && "Type already converted!");
-        continue;
-      }
-      // If the type used to be incomplete then a opaque struct placeholder may
-      // have been created for it already.
-      Type *Ty = GET_TYPE_LLVM(some_type);
-      if (Ty) {
-        assert(isa<StructType>(Ty) && cast<StructType>(Ty)->isOpaque() &&
-               "Recursive struct already fully converted!");
-        continue;
-      }
-      // Otherwise register a placeholder for this type.
-      Ty = StructType::createNamed(Context, getDescriptiveName(some_type));
-      SET_TYPE_LLVM(some_type, Ty);
-    }
-
-    // Now convert every type in the SCC, filling in the placeholders created
-    // above.  In the common case there is only one type in the SCC, meaning
-    // that the type turned out not to be self-recursive and can be converted
-    // without having to worry about type conversion loops.  If there is more
-    // than one type in the SCC then self-recursion is overcome by returning
-    // {}* for the pointer types if nothing better can be done.  As back edges
-    // in the type graph can only be created by pointer types, "removing" such
-    // edges like this destroys all cycles allowing the other types in the SCC
-    // to be converted straightforwardly.
-    SCCInProgress = &SCC;
-    for (unsigned i = 0, e = SCC.size(); i != e; ++i)
-      ConvertType(SCC[i]);
-    SCCInProgress = 0;
-  }
-
-  // At this point every type reachable from this one has been converted, and
-  // the conversion results cached.  Return the value computed for the type.
-  Type *Ty = GET_TYPE_LLVM(type);
-  assert(Ty && "Type not converted!");
-  return Ty;
-}
-
-//===----------------------------------------------------------------------===//
-//                  FUNCTION/METHOD_TYPE Conversion Routines
-//===----------------------------------------------------------------------===//
-
-namespace {
-  class FunctionTypeConversion : public DefaultABIClient {
-    Type *&RetTy;
-    SmallVectorImpl<Type*> &ArgTypes;
-    CallingConv::ID &CallingConv;
-    bool isShadowRet;
-    bool KNRPromotion;
-    unsigned Offset;
-  public:
-    FunctionTypeConversion(Type *&retty, SmallVectorImpl<Type*> &AT,
-                           CallingConv::ID &CC, bool KNR)
-      : RetTy(retty), ArgTypes(AT), CallingConv(CC), KNRPromotion(KNR),
-        Offset(0) {
-      CallingConv = CallingConv::C;
-      isShadowRet = false;
-    }
-
-    /// getCallingConv - This provides the desired CallingConv for the function.
-    CallingConv::ID getCallingConv(void) { return CallingConv; }
-
-    bool isShadowReturn() const { return isShadowRet; }
-
-    /// HandleScalarResult - This callback is invoked if the function returns a
-    /// simple scalar result value.
-    void HandleScalarResult(Type *RetTy) {
-      this->RetTy = RetTy;
-    }
-
-    /// HandleAggregateResultAsScalar - This callback is invoked if the function
-    /// returns an aggregate value by bit converting it to the specified scalar
-    /// type and returning that.
-    void HandleAggregateResultAsScalar(Type *ScalarTy, unsigned Offset=0) {
-      RetTy = ScalarTy;
-      this->Offset = Offset;
-    }
-
-    /// HandleAggregateResultAsAggregate - This callback is invoked if the function
-    /// returns an aggregate value using multiple return values.
-    void HandleAggregateResultAsAggregate(Type *AggrTy) {
-      RetTy = AggrTy;
-    }
-
-    /// HandleShadowResult - Handle an aggregate or scalar shadow argument.
-    void HandleShadowResult(PointerType *PtrArgTy, bool RetPtr) {
-      // This function either returns void or the shadow argument,
-      // depending on the target.
-      RetTy = RetPtr ? PtrArgTy : Type::getVoidTy(Context);
-
-      // In any case, there is a dummy shadow argument though!
-      ArgTypes.push_back(PtrArgTy);
-
-      // Also, note the use of a shadow argument.
-      isShadowRet = true;
-    }
-
-    /// HandleAggregateShadowResult - This callback is invoked if the function
-    /// returns an aggregate value by using a "shadow" first parameter, which is
-    /// a pointer to the aggregate, of type PtrArgTy.  If RetPtr is set to true,
-    /// the pointer argument itself is returned from the function.
-    void HandleAggregateShadowResult(PointerType *PtrArgTy,
-                                       bool RetPtr) {
-      HandleShadowResult(PtrArgTy, RetPtr);
-    }
-
-    /// HandleScalarShadowResult - This callback is invoked if the function
-    /// returns a scalar value by using a "shadow" first parameter, which is a
-    /// pointer to the scalar, of type PtrArgTy.  If RetPtr is set to true,
-    /// the pointer argument itself is returned from the function.
-    void HandleScalarShadowResult(PointerType *PtrArgTy, bool RetPtr) {
-      HandleShadowResult(PtrArgTy, RetPtr);
-    }
-
-    void HandlePad(llvm::Type *LLVMTy) {
-      HandleScalarArgument(LLVMTy, 0, 0);
-    }
-
-    void HandleScalarArgument(llvm::Type *LLVMTy, tree type,
-                              unsigned /*RealSize*/ = 0) {
-      if (KNRPromotion) {
-        if (type == float_type_node)
-          LLVMTy = ConvertType(double_type_node);
-        else if (LLVMTy->isIntegerTy(16) || LLVMTy->isIntegerTy(8) ||
-                 LLVMTy->isIntegerTy(1))
-          LLVMTy = Type::getInt32Ty(Context);
-      }
-      ArgTypes.push_back(LLVMTy);
-    }
-
-    /// HandleByInvisibleReferenceArgument - This callback is invoked if a pointer
-    /// (of type PtrTy) to the argument is passed rather than the argument itself.
-    void HandleByInvisibleReferenceArgument(llvm::Type *PtrTy,
-                                            tree /*type*/) {
-      ArgTypes.push_back(PtrTy);
-    }
-
-    /// HandleByValArgument - This callback is invoked if the aggregate function
-    /// argument is passed by value. It is lowered to a parameter passed by
-    /// reference with an additional parameter attribute "ByVal".
-    void HandleByValArgument(llvm::Type *LLVMTy, tree type) {
-      HandleScalarArgument(LLVMTy->getPointerTo(), type);
-    }
+  // Check for 'readnone' function attribute.
+  // Both PURE and CONST will be set if the user applied
+  // __attribute__((const)) to a function the compiler
+  // knows to be pure, such as log.  A user or (more
+  // likely) libm implementor might know their local log
+  // is in fact const, so this should be valid (and gcc
+  // accepts it).  But llvm IR does not allow both, so
+  // set only ReadNone.
+  if (flags & ECF_CONST)
+    FnAttributes |= Attribute::ReadNone;
 
-    /// HandleFCAArgument - This callback is invoked if the aggregate function
-    /// argument is a first class aggregate passed by value.
-    void HandleFCAArgument(llvm::Type *LLVMTy, tree /*type*/) {
-      ArgTypes.push_back(LLVMTy);
-    }
-  };
-}
+  // Check for 'readonly' function attribute.
+  if (flags & ECF_PURE && !(flags & ECF_CONST))
+    FnAttributes |= Attribute::ReadOnly;
 
+  // Since they write the return value through a pointer,
+  // 'sret' functions cannot be 'readnone' or 'readonly'.
+  if (ABIConverter.isShadowReturn())
+    FnAttributes &= ~(Attribute::ReadNone|Attribute::ReadOnly);
 
-static Attributes HandleArgumentExtension(tree ArgTy) {
-  if (TREE_CODE(ArgTy) == BOOLEAN_TYPE) {
-    if (TREE_INT_CST_LOW(TYPE_SIZE(ArgTy)) < INT_TYPE_SIZE)
-      return Attribute::ZExt;
-  } else if (TREE_CODE(ArgTy) == INTEGER_TYPE &&
-             TREE_INT_CST_LOW(TYPE_SIZE(ArgTy)) < INT_TYPE_SIZE) {
-    if (TYPE_UNSIGNED(ArgTy))
-      return Attribute::ZExt;
-    else
-      return Attribute::SExt;
+  // Demote 'readnone' nested functions to 'readonly' since
+  // they may need to read through the static chain.
+  if (static_chain && (FnAttributes & Attribute::ReadNone)) {
+    FnAttributes &= ~Attribute::ReadNone;
+    FnAttributes |= Attribute::ReadOnly;
   }
 
-  return Attribute::None;
-}
-
-/// ConvertParamListToLLVMSignature - This method is used to build the argument
-/// type list for K&R prototyped functions.  In this case, we have to figure out
-/// the type list (to build a FunctionType) from the actual DECL_ARGUMENTS list
-/// for the function.  This method takes the DECL_ARGUMENTS list (Args), and
-/// fills in Result with the argument types for the function.  It returns the
-/// specified result type for the function.
-FunctionType *TypeConverter::
-ConvertArgListToFnType(tree type, tree Args, tree static_chain,
-                       CallingConv::ID &CallingConv, AttrListPtr &PAL) {
-  tree ReturnType = TREE_TYPE(type);
-  SmallVector<Type*, 8> ArgTys;
-  Type *RetTy(Type::getVoidTy(Context));
-
-  FunctionTypeConversion Client(RetTy, ArgTys, CallingConv, true /*K&R*/);
-  DefaultABI ABIConverter(Client);
-
-#ifdef TARGET_ADJUST_LLVM_CC
-  TARGET_ADJUST_LLVM_CC(CallingConv, type);
-#endif
-
-  // Builtins are always prototyped, so this isn't one.
-  ABIConverter.HandleReturnType(ReturnType, current_function_decl, false);
-
-  SmallVector<AttributeWithIndex, 8> Attrs;
-
   // Compute whether the result needs to be zext or sext'd.
-  Attributes RAttributes = HandleArgumentExtension(ReturnType);
+  Attributes RAttributes = Attribute::None;
+  RAttributes |= HandleArgumentExtension(TREE_TYPE(type));
 
   // Allow the target to change the attributes.
 #ifdef TARGET_ADJUST_LLVM_RETATTR
   TARGET_ADJUST_LLVM_RETATTR(RAttributes, type);
 #endif
 
+  // The value returned by a 'malloc' function does not alias anything.
+  if (flags & ECF_MALLOC)
+    RAttributes |= Attribute::NoAlias;
+
   if (RAttributes != Attribute::None)
     Attrs.push_back(AttributeWithIndex::get(0, RAttributes));
 
   // If this function returns via a shadow argument, the dest loc is passed
   // in as a pointer.  Mark that pointer as struct-ret and noalias.
   if (ABIConverter.isShadowReturn())
-    Attrs.push_back(AttributeWithIndex::get(ArgTys.size(),
+    Attrs.push_back(AttributeWithIndex::get(ArgTypes.size(),
                                     Attribute::StructRet | Attribute::NoAlias));
 
   std::vector<Type*> ScalarArgs;
@@ -1112,128 +766,20 @@
     // Pass the static chain as the first parameter.
     ABIConverter.HandleArgument(TREE_TYPE(static_chain), ScalarArgs);
     // Mark it as the chain argument.
-    Attrs.push_back(AttributeWithIndex::get(ArgTys.size(),
+    Attrs.push_back(AttributeWithIndex::get(ArgTypes.size(),
                                              Attribute::Nest));
   }
 
-  for (; Args && TREE_TYPE(Args) != void_type_node; Args = TREE_CHAIN(Args)) {
-    tree ArgTy = TREE_TYPE(Args);
-
-    // Determine if there are any attributes for this param.
-    Attributes PAttributes = Attribute::None;
-
-    ABIConverter.HandleArgument(ArgTy, ScalarArgs, &PAttributes);
+  // If the target has regparam parameters, allow it to inspect the function
+  // type.
+  int local_regparam = 0;
+  int local_fp_regparam = 0;
+#ifdef LLVM_TARGET_ENABLE_REGPARM
+  LLVM_TARGET_INIT_REGPARM(local_regparam, local_fp_regparam, type);
+#endif // LLVM_TARGET_ENABLE_REGPARM
 
-    // Compute zext/sext attributes.
-    PAttributes |= HandleArgumentExtension(ArgTy);
-
-    if (PAttributes != Attribute::None)
-      Attrs.push_back(AttributeWithIndex::get(ArgTys.size(), PAttributes));
-  }
-
-  PAL = AttrListPtr::get(Attrs.begin(), Attrs.end());
-  return FunctionType::get(RetTy, ArgTys, false);
-}
-
-FunctionType *TypeConverter::
-ConvertFunctionType(tree type, tree decl, tree static_chain,
-                    CallingConv::ID &CallingConv, AttrListPtr &PAL) {
-  Type *RetTy = Type::getVoidTy(Context);
-  SmallVector<Type*, 8> ArgTypes;
-  bool isVarArg = false;
-  FunctionTypeConversion Client(RetTy, ArgTypes, CallingConv, false/*not K&R*/);
-  DefaultABI ABIConverter(Client);
-
-  // Allow the target to set the CC for things like fastcall etc.
-#ifdef TARGET_ADJUST_LLVM_CC
-  TARGET_ADJUST_LLVM_CC(CallingConv, type);
-#endif
-
-  ABIConverter.HandleReturnType(TREE_TYPE(type), current_function_decl,
-                                decl ? DECL_BUILT_IN(decl) : false);
-
-  // Compute attributes for return type (and function attributes).
-  SmallVector<AttributeWithIndex, 8> Attrs;
-  Attributes FnAttributes = Attribute::None;
-
-  int flags = flags_from_decl_or_type(decl ? decl : type);
-
-  // Check for 'noreturn' function attribute.
-  if (flags & ECF_NORETURN)
-    FnAttributes |= Attribute::NoReturn;
-
-  // Check for 'nounwind' function attribute.
-  if (flags & ECF_NOTHROW)
-    FnAttributes |= Attribute::NoUnwind;
-
-  // Check for 'readnone' function attribute.
-  // Both PURE and CONST will be set if the user applied
-  // __attribute__((const)) to a function the compiler
-  // knows to be pure, such as log.  A user or (more
-  // likely) libm implementor might know their local log
-  // is in fact const, so this should be valid (and gcc
-  // accepts it).  But llvm IR does not allow both, so
-  // set only ReadNone.
-  if (flags & ECF_CONST)
-    FnAttributes |= Attribute::ReadNone;
-
-  // Check for 'readonly' function attribute.
-  if (flags & ECF_PURE && !(flags & ECF_CONST))
-    FnAttributes |= Attribute::ReadOnly;
-
-  // Since they write the return value through a pointer,
-  // 'sret' functions cannot be 'readnone' or 'readonly'.
-  if (ABIConverter.isShadowReturn())
-    FnAttributes &= ~(Attribute::ReadNone|Attribute::ReadOnly);
-
-  // Demote 'readnone' nested functions to 'readonly' since
-  // they may need to read through the static chain.
-  if (static_chain && (FnAttributes & Attribute::ReadNone)) {
-    FnAttributes &= ~Attribute::ReadNone;
-    FnAttributes |= Attribute::ReadOnly;
-  }
-
-  // Compute whether the result needs to be zext or sext'd.
-  Attributes RAttributes = Attribute::None;
-  RAttributes |= HandleArgumentExtension(TREE_TYPE(type));
-
-  // Allow the target to change the attributes.
-#ifdef TARGET_ADJUST_LLVM_RETATTR
-  TARGET_ADJUST_LLVM_RETATTR(RAttributes, type);
-#endif
-
-  // The value returned by a 'malloc' function does not alias anything.
-  if (flags & ECF_MALLOC)
-    RAttributes |= Attribute::NoAlias;
-
-  if (RAttributes != Attribute::None)
-    Attrs.push_back(AttributeWithIndex::get(0, RAttributes));
-
-  // If this function returns via a shadow argument, the dest loc is passed
-  // in as a pointer.  Mark that pointer as struct-ret and noalias.
-  if (ABIConverter.isShadowReturn())
-    Attrs.push_back(AttributeWithIndex::get(ArgTypes.size(),
-                                    Attribute::StructRet | Attribute::NoAlias));
-
-  std::vector<Type*> ScalarArgs;
-  if (static_chain) {
-    // Pass the static chain as the first parameter.
-    ABIConverter.HandleArgument(TREE_TYPE(static_chain), ScalarArgs);
-    // Mark it as the chain argument.
-    Attrs.push_back(AttributeWithIndex::get(ArgTypes.size(),
-                                             Attribute::Nest));
-  }
-
-  // If the target has regparam parameters, allow it to inspect the function
-  // type.
-  int local_regparam = 0;
-  int local_fp_regparam = 0;
-#ifdef LLVM_TARGET_ENABLE_REGPARM
-  LLVM_TARGET_INIT_REGPARM(local_regparam, local_fp_regparam, type);
-#endif // LLVM_TARGET_ENABLE_REGPARM
-
-  // Keep track of whether we see a byval argument.
-  bool HasByVal = false;
+  // Keep track of whether we see a byval argument.
+  bool HasByVal = false;
 
   // Check if we have a corresponding decl to inspect.
   tree DeclArgs = (decl) ? DECL_ARGUMENTS(decl) : NULL;
@@ -1638,72 +1184,6 @@
   OS.flush();
 }
 
-/// DecodeStructFields - This method decodes the specified field, if it is a
-/// FIELD_DECL, adding or updating the specified StructTypeConversionInfo to
-/// reflect it.  Return true if field is decoded correctly. Otherwise return
-/// false.
-bool TypeConverter::DecodeStructFields(tree Field,
-                                       StructTypeConversionInfo &Info) {
-  // Handle bit-fields specially.
-  if (isBitfield(Field)) {
-    // If this field is forcing packed llvm struct then retry entire struct
-    // layout.
-    if (!Info.isPacked()) {
-      // Unnamed bitfield type does not contribute in struct alignment
-      // computations. Use packed llvm structure in such cases.
-      if (!DECL_NAME(Field))
-        return false;
-      // If this field is packed then the struct may need padding fields
-      // before this field.
-      if (DECL_PACKED(Field))
-        return false;
-      // If Field has user defined alignment and it does not match Ty alignment
-      // then convert to a packed struct and try again.
-      if (TYPE_USER_ALIGN(TREE_TYPE(Field))) {
-        Type *Ty = ConvertType(TREE_TYPE(Field));
-        if (TYPE_ALIGN(TREE_TYPE(Field)) !=
-            8 * Info.getTypeAlignment(Ty))
-          return false;
-      }
-    }
-    DecodeStructBitField(Field, Info);
-    return true;
-  }
-
-  Info.allFieldsAreNotBitFields();
-
-  // Get the starting offset in the record.
-  uint64_t StartOffsetInBits = getFieldOffsetInBits(Field);
-  assert((StartOffsetInBits & 7) == 0 && "Non-bit-field has non-byte offset!");
-  uint64_t StartOffsetInBytes = StartOffsetInBits/8;
-
-  Type *Ty = ConvertType(TREE_TYPE(Field));
-
-  // If this field is packed then the struct may need padding fields
-  // before this field.
-  if (DECL_PACKED(Field) && !Info.isPacked())
-    return false;
-  // Pop any previous elements out of the struct if they overlap with this one.
-  // This can happen when the C++ front-end overlaps fields with tail padding in
-  // C++ classes.
-  else if (!Info.ResizeLastElementIfOverlapsWith(StartOffsetInBytes, Field, Ty)) {
-    // LLVM disagrees as to where this field should go in the natural field
-    // ordering.  Therefore convert to a packed struct and try again.
-    return false;
-  }
-  else if (TYPE_USER_ALIGN(TREE_TYPE(Field))
-           && (unsigned)DECL_ALIGN(Field) != 8 * Info.getTypeAlignment(Ty)
-           && !Info.isPacked()) {
-    // If Field has user defined alignment and it does not match Ty alignment
-    // then convert to a packed struct and try again.
-    return false;
-  } else
-    // At this point, we know that adding the element will happen at the right
-    // offset.  Add it.
-    Info.addElement(Ty, StartOffsetInBytes, Info.getTypeSize(Ty));
-  return true;
-}
-
 /// DecodeStructBitField - This method decodes the specified bit-field, adding
 /// or updating the specified StructTypeConversionInfo to reflect it.
 ///
@@ -1713,8 +1193,7 @@
 /// (potentially multiple) integer fields of integer type.  This ensures that
 /// initialized globals with bitfields can have the initializers for the
 /// bitfields specified.
-void TypeConverter::DecodeStructBitField(tree_node *Field,
-                                         StructTypeConversionInfo &Info) {
+static void DecodeStructBitField(tree Field, StructTypeConversionInfo &Info) {
   unsigned FieldSizeInBits = TREE_INT_CST_LOW(DECL_SIZE(Field));
 
   if (FieldSizeInBits == 0)   // Ignore 'int:0', which just affects layout.
@@ -1847,6 +1326,71 @@
   Info.addNewBitField(FieldSizeInBits, ExtraSizeInBits, FirstUnallocatedByte);
 }
 
+/// DecodeStructFields - This method decodes the specified field, if it is a
+/// FIELD_DECL, adding or updating the specified StructTypeConversionInfo to
+/// reflect it.  Return true if field is decoded correctly. Otherwise return
+/// false.
+static bool DecodeStructFields(tree Field, StructTypeConversionInfo &Info) {
+  // Handle bit-fields specially.
+  if (isBitfield(Field)) {
+    // If this field is forcing packed llvm struct then retry entire struct
+    // layout.
+    if (!Info.isPacked()) {
+      // Unnamed bitfield type does not contribute in struct alignment
+      // computations. Use packed llvm structure in such cases.
+      if (!DECL_NAME(Field))
+        return false;
+      // If this field is packed then the struct may need padding fields
+      // before this field.
+      if (DECL_PACKED(Field))
+        return false;
+      // If Field has user defined alignment and it does not match Ty alignment
+      // then convert to a packed struct and try again.
+      if (TYPE_USER_ALIGN(TREE_TYPE(Field))) {
+        Type *Ty = ConvertType(TREE_TYPE(Field));
+        if (TYPE_ALIGN(TREE_TYPE(Field)) !=
+            8 * Info.getTypeAlignment(Ty))
+          return false;
+      }
+    }
+    DecodeStructBitField(Field, Info);
+    return true;
+  }
+
+  Info.allFieldsAreNotBitFields();
+
+  // Get the starting offset in the record.
+  uint64_t StartOffsetInBits = getFieldOffsetInBits(Field);
+  assert((StartOffsetInBits & 7) == 0 && "Non-bit-field has non-byte offset!");
+  uint64_t StartOffsetInBytes = StartOffsetInBits/8;
+
+  Type *Ty = ConvertType(TREE_TYPE(Field));
+
+  // If this field is packed then the struct may need padding fields
+  // before this field.
+  if (DECL_PACKED(Field) && !Info.isPacked())
+    return false;
+  // Pop any previous elements out of the struct if they overlap with this one.
+  // This can happen when the C++ front-end overlaps fields with tail padding in
+  // C++ classes.
+  else if (!Info.ResizeLastElementIfOverlapsWith(StartOffsetInBytes, Field, Ty)) {
+    // LLVM disagrees as to where this field should go in the natural field
+    // ordering.  Therefore convert to a packed struct and try again.
+    return false;
+  }
+  else if (TYPE_USER_ALIGN(TREE_TYPE(Field))
+           && (unsigned)DECL_ALIGN(Field) != 8 * Info.getTypeAlignment(Ty)
+           && !Info.isPacked()) {
+    // If Field has user defined alignment and it does not match Ty alignment
+    // then convert to a packed struct and try again.
+    return false;
+  } else
+    // At this point, we know that adding the element will happen at the right
+    // offset.  Add it.
+    Info.addElement(Ty, StartOffsetInBytes, Info.getTypeSize(Ty));
+  return true;
+}
+
 /// UnionHasOnlyZeroOffsets - Check if a union type has only members with
 /// offsets that are zero, e.g., no Fortran equivalences.
 static bool UnionHasOnlyZeroOffsets(tree type) {
@@ -1864,8 +1408,7 @@
 /// there are multiple types with the same alignment, select the one with
 /// the largest size. If the type with max. align is smaller than other types,
 /// then we will add padding later on anyway to match union size.
-void TypeConverter::SelectUnionMember(tree type,
-                                      StructTypeConversionInfo &Info) {
+static void SelectUnionMember(tree type, StructTypeConversionInfo &Info) {
   bool FindBiggest = TREE_CODE(type) != QUAL_UNION_TYPE;
 
   Type *UnionTy = 0;
@@ -1952,7 +1495,7 @@
 //
 // For LLVM purposes, we build a new type for B-within-D that
 // has the correct size and layout for that usage.
-Type *TypeConverter::ConvertRECORD(tree type) {
+static Type *ConvertRECORD(tree type) {
   assert(TYPE_SIZE(type) && "Incomplete types should be handled elsewhere!");
 
   assert(GET_TYPE_LLVM(type) && isa<StructType>(GET_TYPE_LLVM(type)) &&
@@ -2052,3 +1595,462 @@
 
   return ResultTy;
 }
+
+/// mayRecurse - Return true if converting this type may require breaking a
+/// self-referential type loop.  For example, converting the struct type
+///   struct S;
+///   struct S {
+///     struct S* s;
+///   };
+/// requires converting the "struct S*" field type; converting that pointer
+/// type requires converting "struct S", leading to an infinite loop.  On the
+/// other hand simple types like integers are never self-referential.  As this
+/// routine is intended to be quick and simple, it returns true when in doubt.
+/// Note that if a complicated type has already been converted then false is
+/// usually returned, since type conversion doesn't have to do anything except
+/// return the previously computed LLVM type.  The exception is record or union
+/// types which were first converted when incomplete but that are now complete
+/// so need to be converted again.
+static bool mayRecurse(tree type) {
+  assert(type == TYPE_MAIN_VARIANT(type) && "Not converting the main variant!");
+  switch (TREE_CODE(type)) {
+  default:
+    assert(false && "Unknown type!");
+
+  case BOOLEAN_TYPE:
+  case ENUMERAL_TYPE:
+  case FIXED_POINT_TYPE:
+  case INTEGER_TYPE:
+  case OFFSET_TYPE:
+  case REAL_TYPE:
+  case VOID_TYPE:
+    // Simple types that are never self-referential.
+    return false;
+
+  case COMPLEX_TYPE:
+  case VECTOR_TYPE:
+    // Converting these types does involve converting another type, however that
+    // conversion cannot refer back to the initial type.
+    // NOTE: GCC supports vectors of pointers, and the pointer could refer back
+    // to the vector.  However as LLVM does not support vectors of pointers we
+    // don't convert the pointer type and just use an integer instead, so as far
+    // as we are concerned such vector types are not self-referential.
+    return false;
+
+  case ARRAY_TYPE:
+  case FUNCTION_TYPE:
+  case METHOD_TYPE:
+  case POINTER_TYPE:
+  case REFERENCE_TYPE:
+    // Converting these types may recurse unless the type was already converted.
+    return !llvm_has_type(type);
+
+  case QUAL_UNION_TYPE:
+  case RECORD_TYPE:
+  case UNION_TYPE: {
+    // Converting these types may recurse unless already converted.  However if
+    // the type was converted when still incomplete but is now complete then it
+    // needs to be converted again, which might recurse.
+
+    // If the type is incomplete then converting it will not recurse (conversion
+    // just returns an opaque type).
+    if (!TYPE_SIZE(type))
+      return false;
+
+    // If the type was not previously converted then converting it may recurse.
+    Type *Ty = GET_TYPE_LLVM(type);
+    if (!Ty)
+      return true;
+
+    // If the type was previously converted when incomplete then converting it
+    // may recurse as the type is now complete so needs to be converted again.
+    if (cast<StructType>(Ty)->isOpaque())
+      return true;
+
+    // The type was already converted and does not need to be converted again.
+    return false;
+  }
+  }
+}
+
+/// RecursiveTypeIterator - A convenience class that visits only those nodes
+/// in the type graph that mayRecurse thinks might be self-referential.  Note
+/// that dereferencing returns the main variant of the contained type rather
+/// than the contained type itself.  See ContainedTypeIterator and mayRecurse
+/// for more information about the type graph and self-referential types.
+namespace {
+
+  class RecursiveTypeIterator {
+    // This class wraps an iterator that visits all contained types, and just
+    // increments the iterator over any contained types that will not recurse.
+    ContainedTypeIterator I;
+
+    /// SkipNonRecursiveTypes - Increment the wrapped iterator over any types
+    /// that mayRecurse says can be converted directly without having to worry
+    /// about self-recursion.
+    void SkipNonRecursiveTypes() {
+      while (I != ContainedTypeIterator::end() &&
+             !mayRecurse(TYPE_MAIN_VARIANT(*I)))
+        ++I;
+    }
+
+    /// RecursiveTypeIterator - Convenience constructor for internal use.
+    explicit RecursiveTypeIterator(const ContainedTypeIterator& i) : I(i) {}
+
+  public:
+
+    /// Dereference operator returning the main variant of the contained type.
+    tree operator*() {
+      return TYPE_MAIN_VARIANT(*I);
+    };
+
+    /// Comparison operators.
+    bool operator==(const RecursiveTypeIterator &other) const {
+      return other.I == this->I;
+    }
+    bool operator!=(const RecursiveTypeIterator &other) const {
+      return !(*this == other);
+    }
+
+    /// Postfix increment operator.
+    RecursiveTypeIterator operator++(int) {
+      RecursiveTypeIterator Result(*this);
+      ++(*this);
+      return Result;
+    }
+
+    /// Prefix increment operator.
+    RecursiveTypeIterator& operator++() {
+      ++I;
+      SkipNonRecursiveTypes();
+      return *this;
+    }
+
+    /// begin - Return an iterator referring to the first type contained in the
+    /// given type.
+    static RecursiveTypeIterator begin(tree type) {
+      RecursiveTypeIterator R(ContainedTypeIterator::begin(type));
+      R.SkipNonRecursiveTypes();
+      return R;
+    }
+
+    /// end - Return the end iterator for contained type iteration.
+    static RecursiveTypeIterator end() {
+      return RecursiveTypeIterator(ContainedTypeIterator::end());
+    }
+  };
+
+} // Unnamed namespace.
+
+// Traits for working with the graph of possibly self-referential type nodes,
+// see RecursiveTypeIterator.
+namespace llvm {
+  template <> struct GraphTraits<tree> {
+    typedef tree_node NodeType;
+    typedef RecursiveTypeIterator ChildIteratorType;
+    static inline NodeType *getEntryNode(tree t) {
+      assert(TYPE_P(t) && "Expected a type!");
+      return t;
+    }
+    static inline ChildIteratorType child_begin(tree type) {
+      return ChildIteratorType::begin(type);
+    }
+    static inline ChildIteratorType child_end(tree) {
+      return ChildIteratorType::end();
+    }
+  };
+}
+
+/// ConvertNonRecursiveType - Convert a type when this is known to not require
+/// breaking type conversion loops, see mayRecurse.
+static Type *ConvertNonRecursiveType(tree type) {
+  assert(type == TYPE_MAIN_VARIANT(type) && "Not converting the main variant!");
+  assert(!mayRecurse(type) && "Expected a non-recursive type!");
+
+  switch (TREE_CODE(type)) {
+  default:
+    DieAbjectly("Unknown or recursive type!", type);
+
+  case ARRAY_TYPE:
+  case FUNCTION_TYPE:
+  case METHOD_TYPE:
+  case POINTER_TYPE:
+  case REFERENCE_TYPE: {
+    // If these types are not recursive it can only be because they were already
+    // converted and we can safely return the result of the previous conversion.
+    Type *Ty = GET_TYPE_LLVM(type);
+    assert(Ty && "Type not already converted!");
+    return Ty;
+  }
+
+  case ENUMERAL_TYPE:
+    // If the enum is incomplete return a placeholder type.
+    if (!TYPE_SIZE(type))
+      return Type::getInt32Ty(Context);
+    // Otherwise fall through.
+  case BOOLEAN_TYPE:
+  case INTEGER_TYPE: {
+    uint64_t Size = getInt64(TYPE_SIZE(type), true);
+    return IntegerType::get(Context, Size); // Not worth caching.
+  }
+
+  case COMPLEX_TYPE: {
+    if (Type *Ty = GET_TYPE_LLVM(type)) return Ty;
+    Type *Ty = ConvertNonRecursiveType(TYPE_MAIN_VARIANT(TREE_TYPE(type)));
+    Ty = StructType::get(Ty, Ty, NULL);
+    return SET_TYPE_LLVM(type, Ty);
+  }
+
+  case OFFSET_TYPE:
+    // Handle OFFSET_TYPE specially.  This is used for pointers to members,
+    // which are really just integer offsets.  Return the appropriate integer
+    // type directly.
+    return getTargetData().getIntPtrType(Context); // Not worth caching.
+
+  case REAL_TYPE:
+    // It is not worth caching the result of this type conversion.
+    switch (TYPE_PRECISION(type)) {
+    default:
+      DieAbjectly("Unknown FP type!", type);
+    case 32: return Type::getFloatTy(Context);
+    case 64: return Type::getDoubleTy(Context);
+    case 80: return Type::getX86_FP80Ty(Context);
+    case 128:
+#ifdef TARGET_POWERPC
+      return Type::getPPC_FP128Ty(Context);
+#else
+      // IEEE quad precision.
+      return Type::getFP128Ty(Context);
+#endif
+    }
+
+  case RECORD_TYPE:
+  case QUAL_UNION_TYPE:
+  case UNION_TYPE:
+    // If the type was already converted then return the already computed type.
+    if (Type *Ty = GET_TYPE_LLVM(type)) return Ty;
+
+    // Otherwise this must be an incomplete type - return an opaque struct.
+    assert(!TYPE_SIZE(type) && "Expected an incomplete type!");
+    return SET_TYPE_LLVM(type, StructType::createNamed(Context,
+                                                     getDescriptiveName(type)));
+
+  case VECTOR_TYPE: {
+    if (Type *Ty = GET_TYPE_LLVM(type)) return Ty;
+    Type *Ty;
+    // LLVM does not support vectors of pointers, so turn any pointers into
+    // integers.
+    if (POINTER_TYPE_P(TREE_TYPE(type)))
+      Ty = getTargetData().getIntPtrType(Context);
+    else
+      Ty = ConvertNonRecursiveType(TYPE_MAIN_VARIANT(TREE_TYPE(type)));
+    Ty = VectorType::get(Ty, TYPE_VECTOR_SUBPARTS(type));
+    return SET_TYPE_LLVM(type, Ty);
+  }
+
+  case VOID_TYPE:
+    return Type::getVoidTy(Context); // Not worth caching.
+  }
+}
+
+/// ConvertRecursiveType - Convert a type when conversion may require breaking
+/// type conversion loops, see mayRecurse.  Note that all types used by but not
+/// in the current strongly connected component (SCC) must have been converted
+/// already.
+static Type *ConvertRecursiveType(tree type) {
+  assert(type == TYPE_MAIN_VARIANT(type) && "Not converting the main variant!");
+  assert(mayRecurse(type) && "Expected a recursive type!");
+  assert(SCCInProgress && "Missing recursion data!");
+
+#ifndef NDEBUG
+  // Check that the given type is in the current strongly connected component
+  // (SCC) of the type graph.  This should always be the case because SCCs are
+  // visited bottom up.
+  bool inSCC = false;
+  for (unsigned i = 0, e = SCCInProgress->size(); i != e; ++i)
+    if ((*SCCInProgress)[i] == type) {
+      inSCC = true;
+      break;
+    }
+  if (!inSCC)
+    DieAbjectly("Type not in SCC!", type);
+#endif
+
+  switch (TREE_CODE(type)) {
+  default:
+    DieAbjectly("Unexpected type!", type);
+
+  case QUAL_UNION_TYPE:
+  case RECORD_TYPE:
+  case UNION_TYPE:
+    return SET_TYPE_LLVM(type, ConvertRECORD(type));
+
+  case POINTER_TYPE:
+  case REFERENCE_TYPE: {
+    // This is where self-recursion loops are broken, by not converting the type
+    // pointed to if this would cause trouble (the pointer type is turned into
+    // {}* instead).
+    tree pointee = TYPE_MAIN_VARIANT(TREE_TYPE(type));
+
+    // The pointer type is in the strongly connected component (SCC) currently
+    // being converted.  Check whether the pointee is as well.  If there is more
+    // than one type in the SCC then necessarily the pointee type is in the SCC
+    // since any path from the pointer type to the other type necessarily passes
+    // via the pointee.  If the pointer type is the only element of the SCC then
+    // the pointee is only in the SCC if it is equal to the pointer.
+    bool bothInSCC = SCCInProgress->size() != 1 || pointee == type;
+
+    Type *PointeeTy;
+    if (!bothInSCC) {
+      // It is safe to convert the pointee.  This is the common case, as we get
+      // here for pointers to integers and so on.
+      PointeeTy = ConvertType(pointee);
+      if (PointeeTy->isVoidTy())
+        PointeeTy = GetUnitType(Context); // void* -> byte*.
+    } else {
+      // Both the pointer and the pointee type are in the SCC so it is not safe
+      // to convert the pointee type - otherwise we would get an infinite loop.
+      // However if a type, for example an opaque struct placeholder, has been
+      // registered for the pointee then we can return a pointer to it, giving
+      // nicer IR (this is not needed for correctness).  Note that some members
+      // of the SCC may have been converted already at this point (for this to
+      // happen there must be more than one pointer type in the SCC), and thus
+      // will have LLVM types registered for them.  Unfortunately which types
+      // have been converted depends on the order in which we visit the SCC, and
+      // that is not an intrinsic property of the SCC.  This is why we choose to
+      // only use the types registered for records and unions - these are always
+      // available.  As a further attempt to improve the IR, we return an S* for
+      // an array type S[N] if (recursively) S is a record or union type.
+
+      // Drill down through nested arrays to the ultimate element type.  Thanks
+      // to this we may return S* for a (S[])*, which is better than {}*.
+      while (TREE_CODE(pointee) == ARRAY_TYPE)
+        pointee = TYPE_MAIN_VARIANT(TREE_TYPE(pointee));
+
+      // If the pointee is a record or union type then return a pointer to its
+      // placeholder type.  Otherwise return {}*.
+      if (TREE_CODE(pointee) == QUAL_UNION_TYPE ||
+          TREE_CODE(pointee) == RECORD_TYPE ||
+          TREE_CODE(pointee) == UNION_TYPE)
+        PointeeTy = GET_TYPE_LLVM(pointee);
+      else
+        PointeeTy = StructType::get(Context);
+    }
+
+    return SET_TYPE_LLVM(type, PointeeTy->getPointerTo());
+  }
+
+  case METHOD_TYPE:
+  case FUNCTION_TYPE: {
+    CallingConv::ID CallingConv;
+    AttrListPtr PAL;
+    // No declaration to pass through, passing NULL.
+    return SET_TYPE_LLVM(type, ConvertFunctionType(type, NULL, NULL,
+                                                   CallingConv, PAL));
+  }
+
+  case ARRAY_TYPE: {
+    Type *ElementTy = ConvertType(TREE_TYPE(type));
+    uint64_t NumElements = ArrayLengthOf(type);
+
+    if (NumElements == NO_LENGTH) // Variable length array?
+      NumElements = 0;
+
+    // Create the array type.
+    Type *Ty = ArrayType::get(ElementTy, NumElements);
+
+    // If the user increased the alignment of the array element type, then the
+    // size of the array is rounded up by that alignment even though the size
+    // of the array element type is not (!).  Correct for this if necessary by
+    // adding padding.  May also need padding if the element type has variable
+    // size and the array type has variable length, but by a miracle the product
+    // gives a constant size.
+    if (isInt64(TYPE_SIZE(type), true)) {
+      uint64_t PadBits = getInt64(TYPE_SIZE(type), true) -
+        getTargetData().getTypeAllocSizeInBits(Ty);
+      if (PadBits) {
+        Type *Padding = ArrayType::get(Type::getInt8Ty(Context), PadBits / 8);
+        Ty = StructType::get(Ty, Padding, NULL);
+      }
+    }
+
+    return SET_TYPE_LLVM(type, Ty);
+  }
+  }
+}
+
+Type *ConvertType(tree type) {
+  if (type == error_mark_node) return Type::getInt32Ty(Context);
+
+  // LLVM doesn't care about variants such as const, volatile, or restrict.
+  type = TYPE_MAIN_VARIANT(type);
+
+  // If this type can be converted without special action being needed to avoid
+  // conversion loops coming from self-referential types, then convert it.
+  if (!mayRecurse(type))
+    return ConvertNonRecursiveType(type);
+
+  // If we already started a possibly looping type conversion, continue with it.
+  if (SCCInProgress)
+    return ConvertRecursiveType(type);
+
+  // Begin converting a type for which the conversion may require breaking type
+  // conversion loops coming from self-referential types, see mayRecurse.  First
+  // analyse all of the types that will need to be converted in order to convert
+  // this one, finding sets of types that must be converted simultaneously (i.e.
+  // for which converting any one of them requires converting all of the others;
+  // these sets are the strongly connected components (SCCs) of the type graph),
+  // then visit them bottom up, converting all types in them.  "Bottom up" means
+  // that if a type in a SCC makes use of a type T that is not in the SCC then T
+  // will be visited first.  Note that this analysis is performed only once: the
+  // results of the type conversion are cached, and any future conversion of one
+  // of the visited types will just return the cached value.
+  for (scc_iterator<tree> I = scc_begin(type), E = scc_end(type); I != E; ++I) {
+    const std::vector<tree> &SCC = *I;
+
+    // First create a placeholder opaque struct for every record or union type
+    // in the SCC.  This way, if we have both "struct S" and "struct S*" in the
+    // SCC then we can return an LLVM "%struct.s*" for the pointer rather than
+    // the nasty {}* type we are obliged to return in general.
+    for (unsigned i = 0, e = SCC.size(); i != e; ++i) {
+      tree some_type = SCC[i];
+      if (TREE_CODE(some_type) != QUAL_UNION_TYPE &&
+          TREE_CODE(some_type) != RECORD_TYPE &&
+          TREE_CODE(some_type) != UNION_TYPE) {
+        assert(!llvm_has_type(some_type) && "Type already converted!");
+        continue;
+      }
+      // If the type used to be incomplete then a opaque struct placeholder may
+      // have been created for it already.
+      Type *Ty = GET_TYPE_LLVM(some_type);
+      if (Ty) {
+        assert(isa<StructType>(Ty) && cast<StructType>(Ty)->isOpaque() &&
+               "Recursive struct already fully converted!");
+        continue;
+      }
+      // Otherwise register a placeholder for this type.
+      Ty = StructType::createNamed(Context, getDescriptiveName(some_type));
+      SET_TYPE_LLVM(some_type, Ty);
+    }
+
+    // Now convert every type in the SCC, filling in the placeholders created
+    // above.  In the common case there is only one type in the SCC, meaning
+    // that the type turned out not to be self-recursive and can be converted
+    // without having to worry about type conversion loops.  If there is more
+    // than one type in the SCC then self-recursion is overcome by returning
+    // {}* for the pointer types if nothing better can be done.  As back edges
+    // in the type graph can only be created by pointer types, "removing" such
+    // edges like this destroys all cycles allowing the other types in the SCC
+    // to be converted straightforwardly.
+    SCCInProgress = &SCC;
+    for (unsigned i = 0, e = SCC.size(); i != e; ++i)
+      ConvertType(SCC[i]);
+    SCCInProgress = 0;
+  }
+
+  // At this point every type reachable from this one has been converted, and
+  // the conversion results cached.  Return the value computed for the type.
+  Type *Ty = GET_TYPE_LLVM(type);
+  assert(Ty && "Type not converted!");
+  return Ty;
+}





More information about the llvm-commits mailing list