diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index ef99ebc1131670d70ec7d681aabace8896b6d91e..661db5a84e780392c2c4e1f8680646048235050a 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,4 +1,35 @@
-2007-09-06  Jie Zhang  <jie.zhang@analog.com>
+2007-09-05  Uros Bizjak  <ubizjak@gmail.com>
+
+	* gcc/config/i386/cpuid.h: New file.
+	* gcc/config/i386/driver-i386.c: Include cpuid.h.
+	(describe_cache): Shrink size and line strings to 100 bytes.
+	(detect_caches_amd): Return "" for unsupported max_ext_level.
+	Use __cpuid function.
+	(detect_caches_intel): Return "" for unsupported max_level.
+	Use __cpuid function.
+	(host_detect_local_cpu): Change feature flag variables to
+	unsigned int.  Initialize only extended feature flag variables.
+	Use __get_cpuid_max to determine max supported cpuid level.
+	Use __cpuid function to determine supported features.  Fix
+	calculation of family id.  Remove is_amd and check signature
+	directly.  Check for Geode signature.  Handle family 4 id.
+	[PROCESSOR_GENERIC32]: New default for unknown family id.  Move
+	cpu discovery code to lower part of the function.
+	[PROCESSOR_PENTIUM, PROCESSOR_K6, PROCESSOR_ATHLON]: Do not tune
+	for sub-architecture.
+	[PROCESSOR_PENTIUMPRO]: Simplify cpu discovery code.
+	[PROCESSOR_K8]: Add k8-sse3 architecture.
+	[PROCESSOR_NOCONA]: Remove.
+	[PROCESSOR_GENERIC64]: Ditto.
+	* gcc/config/i386/x-i386 (driver-i386.o): Depend on cpuid.h.
+	* gcc/config/i386/crtfastmath.c: Include cpuid.h.  Use __get_cpuid
+	to check for SSE and FXSAVE support.
+	* gcc/config/i386/t-crtfm (crtfastmath.o): Depend on cpuid.h.
+	Add -minline-all-stringops.
+	* gcc/config.gcc (i[34567]86-*-*): Add cpuid.h to extra_headers.
+	(x86_64-*-*): Ditto.
+
+2007-09-05  Jie Zhang  <jie.zhang@analog.com>
 
 	* config/bfin/linux-unwind.h: New file.
 	* config/bfin/linux.h (MD_UNWIND_SUPPORT): Define.
diff --git a/gcc/config.gcc b/gcc/config.gcc
index 75038951ddc84b9211622baed96ed034212d8806..0eecd7ef90c516c754ed7208dce8c8922acef458 100644
--- a/gcc/config.gcc
+++ b/gcc/config.gcc
@@ -278,13 +278,13 @@ xscale-*-*)
 	;;
 i[34567]86-*-*)
 	cpu_type=i386
-	extra_headers="mmintrin.h mm3dnow.h xmmintrin.h emmintrin.h
+	extra_headers="cpuid.h mmintrin.h mm3dnow.h xmmintrin.h emmintrin.h
 		       pmmintrin.h tmmintrin.h ammintrin.h smmintrin.h
 		       nmmintrin.h"
 	;;
 x86_64-*-*)
 	cpu_type=i386
-	extra_headers="mmintrin.h mm3dnow.h xmmintrin.h emmintrin.h
+	extra_headers="cpuid.h mmintrin.h mm3dnow.h xmmintrin.h emmintrin.h
 		       pmmintrin.h tmmintrin.h ammintrin.h smmintrin.h
 		       nmmintrin.h"
 	need_64bit_hwint=yes
diff --git a/gcc/config/i386/cpuid.h b/gcc/config/i386/cpuid.h
new file mode 100644
index 0000000000000000000000000000000000000000..49af88d5e47ccf6ac45eebbb8e16b225dc5ce16d
--- /dev/null
+++ b/gcc/config/i386/cpuid.h
@@ -0,0 +1,133 @@
+/*
+ * Copyright (C) 2007 Free Software Foundation, Inc.
+ *
+ * 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 2, or (at your option) any
+ * later version.
+ * 
+ * In addition to the permissions in the GNU General Public License, the
+ * Free Software Foundation gives you unlimited permission to link the
+ * compiled version of this file with other programs, and to distribute
+ * those programs without any restriction coming from the use of this
+ * file.  (The General Public License restrictions do apply in other
+ * respects; for example, they cover modification of the file, and
+ * distribution when not linked into another program.)
+ * 
+ * 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.
+ * 
+ * You should have received a copy of the GNU General Public License
+ * along with this program; see the file COPYING.  If not, write to
+ * the Free Software Foundation, 51 Franklin Street, Fifth Floor,
+ * Boston, MA 02110-1301, USA.
+ * 
+ *    As a special exception, if you link this library with files
+ *    compiled with GCC to produce an executable, this does not cause
+ *    the resulting executable to be covered by the GNU General Public License.
+ *    This exception does not however invalidate any other reasons why
+ *    the executable file might be covered by the GNU General Public License.
+ */
+
+/* %ecx */
+#define bit_SSE3	(1 << 0)
+#define bit_SSSE3	(1 << 9)
+#define bit_CMPXCHG16B	(1 << 13)
+#define bit_SSE4_1	(1 << 19)
+#define bit_SSE4_2	(1 << 20)
+#define bit_POPCNT	(1 << 23)
+
+/* %edx */
+#define bit_CMPXCHG8B	(1 << 8)
+#define bit_CMOV	(1 << 15)
+#define bit_MMX		(1 << 23)
+#define bit_FXSAVE	(1 << 24)
+#define bit_SSE		(1 << 25)
+#define bit_SSE2	(1 << 26)
+
+/* Extended Features */
+/* %ecx */
+#define bit_LAHF_LM	(1 << 0)
+#define bit_SSE4a	(1 << 6)
+
+/* %edx */
+#define bit_LM		(1 << 29)
+#define bit_3DNOWP	(1 << 30)
+#define bit_3DNOW	(1 << 31)
+
+
+#if defined(__i386__) && defined(__PIC__)
+/* %ebx may be the PIC register.  */
+#define __cpuid(level, a, b, c, d)			\
+  __asm__ ("xchgl\t%%ebx, %1\n\t"			\
+	   "cpuid\n\t"					\
+	   "xchgl\t%%ebx, %1\n\t"			\
+	   : "=a" (a), "=r" (b), "=c" (c), "=d" (d)	\
+	   : "0" (level))
+#else
+#define __cpuid(level, a, b, c, d)			\
+  __asm__ ("cpuid\n\t"					\
+	   : "=a" (a), "=b" (b), "=c" (c), "=d" (d)	\
+	   : "0" (level))
+#endif
+
+/* Return highest supported input value for cpuid instruction.  ext can
+   be either 0x0 or 0x8000000 to return highest supported value for
+   basic or extended cpuid information.  Function returns 0 if cpuid
+   is not supported or whatever cpuid returns in eax register.  If sig
+   pointer is non-null, then first four bytes of the signature
+   (as found in ebx register) are returned in location pointed by sig.  */
+
+static __inline unsigned int
+__get_cpuid_max (unsigned int __ext, unsigned int *__sig)
+{
+  unsigned int __eax, __ebx, __ecx, __edx;
+
+#ifndef __x86_64__
+  /* See if we can use cpuid.  On AMD64 we always can.  */
+  __asm__ ("pushfl\n\t"
+	   "pushfl\n\t"
+	   "popl\t%0\n\t"
+	   "movl\t%0, %1\n\t"
+	   "xorl\t%2, %0\n\t"
+	   "pushl\t%0\n\t"
+	   "popfl\n\t"
+	   "pushfl\n\t"
+	   "popl\t%0\n\t"
+	   "popfl\n\t"
+	   : "=&r" (__eax), "=&r" (__ebx)
+	   : "i" (0x00200000));
+
+  if (!((__eax ^ __ebx) & 0x00200000))
+    return 0;
+#endif
+
+  /* Host supports cpuid.  Return highest supported cpuid input value.  */
+  __cpuid (__ext, __eax, __ebx, __ecx, __edx);
+
+  if (__sig)
+    *__sig = __ebx;
+
+  return __eax;
+}
+
+/* Return cpuid data for requested cpuid level, as found in returned
+   eax, ebx, ecx and edx registers.  The function checks if cpuid is
+   supported and returns 1 for valid cpuid information or 0 for
+   unsupported cpuid level.  All pointers are requred to be non-null.  */
+
+static __inline int
+__get_cpuid (unsigned int __level,
+	     unsigned int *__eax, unsigned int *__ebx,
+	     unsigned int *__ecx, unsigned int *__edx)
+{
+  unsigned int __ext = __level & 0x80000000;
+
+  if (__get_cpuid_max (__ext, 0) < __level)
+    return 0;
+
+  __cpuid (__level, *__eax, *__ebx, *__ecx, *__edx);
+  return 1;
+}
diff --git a/gcc/config/i386/crtfastmath.c b/gcc/config/i386/crtfastmath.c
index 5991442686ab73ad88792712072323e7ae444b4f..19db142d58f26668b6a62d96d2a98a3d6e25aa33 100644
--- a/gcc/config/i386/crtfastmath.c
+++ b/gcc/config/i386/crtfastmath.c
@@ -1,5 +1,5 @@
 /*
- * Copyright (C) 2005 Free Software Foundation, Inc.
+ * Copyright (C) 2005, 2007 Free Software Foundation, Inc.
  *
  * 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
@@ -34,8 +34,11 @@
 #define MXCSR_DAZ (1 << 6)	/* Enable denormals are zero mode */
 #define MXCSR_FTZ (1 << 15)	/* Enable flush to zero mode */
 
-#define FXSAVE	(1 << 24)
-#define SSE	(1 << 25)
+#ifndef __x86_64__
+/* All 64-bit targets have SSE and DAZ;
+   only check them explicitly for 32-bit ones. */
+#include "cpuid.h"
+#endif
 
 static void __attribute__((constructor))
 #ifndef __x86_64__
@@ -47,38 +50,18 @@ __attribute__ ((force_align_arg_pointer))
 set_fast_math (void)
 {
 #ifndef __x86_64__
-  /* All 64-bit targets have SSE and DAZ; only check them explicitly
-     for 32-bit ones. */
   unsigned int eax, ebx, ecx, edx;
 
-  /* See if we can use cpuid.  */
-  asm volatile ("pushfl; pushfl; popl %0; movl %0,%1; xorl %2,%0;"
-		"pushl %0; popfl; pushfl; popl %0; popfl"
-		: "=&r" (eax), "=&r" (ebx)
-		: "i" (0x00200000));
-
-  if (((eax ^ ebx) & 0x00200000) == 0)
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
     return;
 
-  /* Check the highest input value for eax.  */
-  asm volatile ("xchgl %%ebx, %1; cpuid; xchgl %%ebx, %1"
-		: "=a" (eax), "=r" (ebx), "=c" (ecx), "=d" (edx)
-		: "0" (0));
-
-  if (eax == 0)
-    return;
-
-  asm volatile ("xchgl %%ebx, %1; cpuid; xchgl %%ebx, %1"
-		: "=a" (eax), "=r" (ebx), "=c" (ecx), "=d" (edx)
-		: "0" (1));
-
-  if (edx & SSE)
+  if (edx & bit_SSE)
     {
       unsigned int mxcsr = __builtin_ia32_stmxcsr ();
   
       mxcsr |= MXCSR_FTZ;
 
-      if (edx & FXSAVE)
+      if (edx & bit_FXSAVE)
 	{
 	  /* Check if DAZ is available.  */
 	  struct
diff --git a/gcc/config/i386/driver-i386.c b/gcc/config/i386/driver-i386.c
index 5116d8e7504b9f318379837f8c39c7b94f817514..df2fadee713b40767c90193b37ff96dda861021e 100644
--- a/gcc/config/i386/driver-i386.c
+++ b/gcc/config/i386/driver-i386.c
@@ -26,26 +26,7 @@ along with GCC; see the file COPYING3.  If not see
 const char *host_detect_local_cpu (int argc, const char **argv);
 
 #ifdef GCC_VERSION
-#define cpuid(num,a,b,c,d) \
-  asm volatile ("xchgl %%ebx, %1; cpuid; xchgl %%ebx, %1" \
-		: "=a" (a), "=r" (b), "=c" (c), "=d" (d)  \
-		: "0" (num))
-
-#define bit_CMPXCHG8B (1 << 8)
-#define bit_CMOV (1 << 15)
-#define bit_MMX (1 << 23)
-#define bit_SSE (1 << 25)
-#define bit_SSE2 (1 << 26)
-
-#define bit_SSE3 (1 << 0)
-#define bit_SSSE3 (1 << 9)
-#define bit_SSE4a (1 << 6)
-#define bit_CMPXCHG16B (1 << 13)
-
-#define bit_LAHF_LM (1 << 0)
-#define bit_3DNOW (1 << 31)
-#define bit_3DNOWP (1 << 30)
-#define bit_LM (1 << 29)
+#include "cpuid.h"
 
 /* Returns parameters that describe L1_ASSOC associative cache of size
    L1_SIZEKB with lines of size L1_LINE.  */
@@ -54,7 +35,7 @@ static char *
 describe_cache (unsigned l1_sizekb, unsigned l1_line,
 		unsigned l1_assoc ATTRIBUTE_UNUSED)
 {
-  char size[1000], line[1000];
+  char size[100], line[100];
 
   /* At the moment, gcc middle-end does not use the information about the
      associativity of the cache.  */
@@ -74,9 +55,9 @@ detect_caches_amd (unsigned max_ext_level)
   unsigned l1_sizekb, l1_line, l1_assoc;
 
   if (max_ext_level < 0x80000005)
-    return NULL;
+    return (char *) "";
 
-  cpuid (0x80000005, eax, ebx, ecx, edx);
+  __cpuid (0x80000005, eax, ebx, ecx, edx);
 
   l1_line = ecx & 0xff;
   l1_sizekb = (ecx >> 24) & 0xff;
@@ -155,14 +136,15 @@ detect_caches_intel (unsigned max_level)
   unsigned l1_sizekb = 0, l1_line = 0, assoc = 0;
 
   if (max_level < 2)
-    return NULL;
+    return (char *) "";
 
-  cpuid (2, eax, ebx, ecx, edx);
+  __cpuid (2, eax, ebx, ecx, edx);
 
   decode_caches_intel (eax, &l1_sizekb, &l1_line, &assoc);
   decode_caches_intel (ebx, &l1_sizekb, &l1_line, &assoc);
   decode_caches_intel (ecx, &l1_sizekb, &l1_line, &assoc);
   decode_caches_intel (edx, &l1_sizekb, &l1_line, &assoc);
+
   if (!l1_sizekb)
     return (char *) "";
 
@@ -181,88 +163,84 @@ detect_caches_intel (unsigned max_level)
 
    ARGC and ARGV are set depending on the actual arguments given
    in the spec.  */
+
 const char *host_detect_local_cpu (int argc, const char **argv)
 {
-  const char *cpu = NULL;
+  enum processor_type processor = PROCESSOR_I386;
+  const char *cpu = "i386";
+
   const char *cache = "";
   const char *options = "";
-  enum processor_type processor = PROCESSOR_I386;
-  unsigned int eax, ebx, ecx, edx;
-  unsigned int max_level;
+
+ unsigned int eax, ebx, ecx, edx;
+
+  unsigned int max_level, ext_level;
   unsigned int vendor;
-  unsigned int ext_level;
-  unsigned char has_mmx = 0, has_3dnow = 0, has_3dnowp = 0, has_sse = 0;
-  unsigned char has_sse2 = 0, has_sse3 = 0, has_ssse3 = 0, has_cmov = 0;
-  unsigned char has_cmpxchg16b = 0, has_lahf_lm = 0;
-  unsigned char has_longmode = 0, has_cmpxchg8b = 0, has_sse4a = 0;
-  unsigned char is_amd = 0;
-  unsigned int family = 0;
+  unsigned int family;
+
+  unsigned int has_sse3, has_ssse3, has_cmpxchg16b;
+  unsigned int has_cmpxchg8b, has_cmov, has_mmx, has_sse, has_sse2;
+
+  /* Extended features */
+  unsigned int has_lahf_lm = 0, has_sse4a = 0;
+  unsigned int has_longmode = 0, has_3dnowp = 0, has_3dnow = 0;
+
   bool arch;
 
   if (argc < 1)
     return NULL;
 
-  arch = strcmp (argv[0], "arch") == 0;
+  arch = !strcmp (argv[0], "arch");
+
   if (!arch && strcmp (argv[0], "tune"))
     return NULL;
 
-#ifndef __x86_64__
-  /* See if we can use cpuid.  */
-  asm volatile ("pushfl; pushfl; popl %0; movl %0,%1; xorl %2,%0;"
-		"pushl %0; popfl; pushfl; popl %0; popfl"
-		: "=&r" (eax), "=&r" (ebx)
-		: "i" (0x00200000));
-
-  if (((eax ^ ebx) & 0x00200000) == 0)
+  max_level = __get_cpuid_max (0, &vendor);
+  if (max_level < 1)
     goto done;
-#endif
-
-  processor = PROCESSOR_PENTIUM;
 
-  /* Check the highest input value for eax.  */
-  cpuid (0, eax, ebx, ecx, edx);
-  max_level = eax;
-  /* We only look at the first four characters.  */
-  vendor = ebx;
-  if (max_level == 0)
-    goto done;
+  __cpuid (1, eax, ebx, ecx, edx);
 
-  cpuid (1, eax, ebx, ecx, edx);
-  has_cmpxchg8b = !!(edx & bit_CMPXCHG8B);
-  has_cmov = !!(edx & bit_CMOV);
-  has_mmx = !!(edx & bit_MMX);
-  has_sse = !!(edx & bit_SSE);
-  has_sse2 = !!(edx & bit_SSE2);
-  has_sse3 = !!(ecx & bit_SSE3);
-  has_ssse3 = !!(ecx & bit_SSSE3);
-  has_cmpxchg16b = !!(ecx & bit_CMPXCHG16B);
   /* We don't care for extended family.  */
-  family = (eax >> 8) & ~(1 << 4);
+  family = (eax >> 8) & 0x0f;
+
+  has_sse3 = ecx & bit_SSE3;
+  has_ssse3 = ecx & bit_SSSE3;
+  has_cmpxchg16b = ecx & bit_CMPXCHG16B;
 
-  cpuid (0x80000000, eax, ebx, ecx, edx);
-  ext_level = eax;
-  if (ext_level >= 0x80000000)
+  has_cmpxchg8b = edx & bit_CMPXCHG8B;
+  has_cmov = edx & bit_CMOV;
+  has_mmx = edx & bit_MMX;
+  has_sse = edx & bit_SSE;
+  has_sse2 = edx & bit_SSE2;
+
+  /* Check cpuid level of extended features.  */
+  __cpuid (0x80000000, ext_level, ebx, ecx, edx);
+
+  if (ext_level > 0x80000000)
     {
-      cpuid (0x80000001, eax, ebx, ecx, edx);
-      has_lahf_lm = !!(ecx & bit_LAHF_LM);
-      has_3dnow = !!(edx & bit_3DNOW);
-      has_3dnowp = !!(edx & bit_3DNOWP);
-      has_longmode = !!(edx & bit_LM);
-      has_sse4a = !!(ecx & bit_SSE4a);
-    }
+      __cpuid (0x80000001, eax, ebx, ecx, edx);
 
-  is_amd = vendor == *(unsigned int*)"Auth";
+      has_lahf_lm = ecx & bit_LAHF_LM;
+      has_sse4a = ecx & bit_SSE4a;
+
+      has_longmode = edx & bit_LM;
+      has_3dnowp = edx & bit_3DNOWP;
+      has_3dnow = edx & bit_3DNOW;
+    }
 
   if (!arch)
     {
-      if (is_amd)
+      if (vendor == *(unsigned int*) "Auth")
 	cache = detect_caches_amd (ext_level);
-      else if (vendor == *(unsigned int*)"Genu")
+      else if (vendor == *(unsigned int*) "Genu")
 	cache = detect_caches_intel (max_level);
     }
 
-  if (is_amd)
+  if (vendor == *(unsigned int*) "Auth")
     {
+      processor = PROCESSOR_PENTIUM;
+
       if (has_mmx)
 	processor = PROCESSOR_K6;
       if (has_3dnowp)
@@ -272,12 +250,17 @@ const char *host_detect_local_cpu (int argc, const char **argv)
       if (has_sse4a)
 	processor = PROCESSOR_AMDFAM10;
     }
+  else if (vendor == *(unsigned int*) "Geod")
+    processor = PROCESSOR_GEODE;
   else
     {
       switch (family)
 	{
+	case 4:
+	  processor = PROCESSOR_I486;
+	  break;
 	case 5:
-	  /* Default is PROCESSOR_PENTIUM.  */
+	  processor = PROCESSOR_PENTIUM;
 	  break;
 	case 6:
 	  processor = PROCESSOR_PENTIUMPRO;
@@ -286,135 +269,111 @@ const char *host_detect_local_cpu (int argc, const char **argv)
 	  processor = PROCESSOR_PENTIUM4;
 	  break;
 	default:
-	  /* We have no idea.  Use something reasonable.  */
-	  if (arch)
-	    {
-	      if (has_ssse3)
-		cpu = "core2";
-	      else if (has_sse3)
-		{
-		  if (has_longmode)
-		    cpu = "nocona";
-		  else
-		    cpu = "prescott";
-		}
-	      else if (has_sse2)
-		cpu = "pentium4";
-	      else if (has_cmov)
-		cpu = "pentiumpro";
-	      else if (has_mmx)
-		cpu = "pentium-mmx";
-	      else if (has_cmpxchg8b)
-		cpu = "pentium";
-	      else
-		cpu = "i386";
-	    }
-	  else
-	    cpu = "generic";
-	  goto done;
-	  break;
+	  /* We have no idea.  */
+	  processor = PROCESSOR_GENERIC32;
 	}
     }
 
   switch (processor)
     {
     case PROCESSOR_I386:
-      cpu = "i386";
+      /* Default.  */
       break;
     case PROCESSOR_I486:
       cpu = "i486";
       break;
     case PROCESSOR_PENTIUM:
-      if (has_mmx)
+      if (arch && has_mmx)
 	cpu = "pentium-mmx";
       else
 	cpu = "pentium";
       break;
     case PROCESSOR_PENTIUMPRO:
       if (has_longmode)
+	/* It is Core 2 Duo.  */
+	cpu = "core2";
+      else if (arch)
 	{
-	  /* It is Core 2 Duo.  */
-	  cpu = "core2";
+	  if (has_sse3)
+	    /* It is Core Duo.  */
+	    cpu = "prescott";
+	  else if (has_sse2)
+	    /* It is Pentium M.  */
+	    cpu = "pentium-m";
+	  else if (has_sse)
+	    /* It is Pentium III.  */
+	    cpu = "pentium3";
+	  else if (has_mmx)
+	    /* It is Pentium II.  */
+	    cpu = "pentium2";
+	  else
+	    /* Default to Pentium Pro.  */
+	    cpu = "pentiumpro";
 	}
       else
+	/* For -mtune, we default to -mtune=generic.  */
+	cpu = "generic";
+      break;
+    case PROCESSOR_PENTIUM4:
+      if (has_sse3)
 	{
-	  if (arch)
-	    {
-	      if (has_sse3)
-		{
-		  /* It is Core Duo.  */
-		  cpu = "prescott";
-		}
-	      else if (has_sse2)
-		{
-		  /* It is Pentium M.  */
-		  cpu = "pentium4";
-		}
-	      else if (has_sse)
-		{
-		  /* It is Pentium III.  */
-		  cpu = "pentium3";
-		}
-	      else if (has_mmx)
-		{
-		  /* It is Pentium II.  */
-		  cpu = "pentium2";
-		}
-	      else
-		{
-		  /* Default to Pentium Pro.  */
-		  cpu = "pentiumpro";
-		}
-	    }
+	  if (has_longmode)
+	    cpu = "nocona";
 	  else
-	    {
-	      /* For -mtune, we default to -mtune=generic.  */
-	      cpu = "generic";
-	    }
+	    cpu = "prescott";
 	}
+      else
+	cpu = "pentium4";
       break;
     case PROCESSOR_GEODE:
       cpu = "geode";
       break;
     case PROCESSOR_K6:
-      if (has_3dnow)
-        cpu = "k6-3";
+      if (arch && has_3dnow)
+	cpu = "k6-3";
       else
 	cpu = "k6";
       break;
     case PROCESSOR_ATHLON:
-      if (has_sse)
+      if (arch && has_sse)
 	cpu = "athlon-4";
       else
 	cpu = "athlon";
       break;
-    case PROCESSOR_PENTIUM4:
-      if (has_sse3)
-	{
-	  if (has_longmode)
-	    cpu = "nocona";
-	  else
-	    cpu = "prescott";
-	}
-      else
-	cpu = "pentium4";
-      break;
     case PROCESSOR_K8:
-      cpu = "k8";
-      break;
-    case PROCESSOR_NOCONA:
-      cpu = "nocona";
+      if (arch && has_sse3)
+	cpu = "k8-sse3";
+      else
+	cpu = "k8";
       break;
     case PROCESSOR_AMDFAM10:
       cpu = "amdfam10";
       break;
-    case PROCESSOR_GENERIC32:
-    case PROCESSOR_GENERIC64:
-      cpu = "generic";
-      break;
+
     default:
-      abort ();
-      break;
+      /* Use something reasonable.  */
+      if (arch)
+	{
+	  if (has_ssse3)
+	    cpu = "core2";
+	  else if (has_sse3)
+	    {
+	      if (has_longmode)
+		cpu = "nocona";
+	      else
+		cpu = "prescott";
+	    }
+	  else if (has_sse2)
+	    cpu = "pentium4";
+	  else if (has_cmov)
+	    cpu = "pentiumpro";
+	  else if (has_mmx)
+	    cpu = "pentium-mmx";
+	  else if (has_cmpxchg8b)
+	    cpu = "pentium";
+	}
+      else
+	cpu = "generic";
     }
 
   if (arch)
@@ -429,8 +388,10 @@ done:
   return concat (cache, "-m", argv[0], "=", cpu, " ", options, NULL);
 }
 #else
+
 /* If we aren't compiling with GCC we just provide a minimal
    default value.  */
+
 const char *host_detect_local_cpu (int argc, const char **argv)
 {
   const char *cpu;
@@ -439,7 +400,8 @@ const char *host_detect_local_cpu (int argc, const char **argv)
   if (argc < 1)
     return NULL;
 
-  arch = strcmp (argv[0], "arch") == 0;
+  arch = !strcmp (argv[0], "arch");
+
   if (!arch && strcmp (argv[0], "tune"))
     return NULL;
   
diff --git a/gcc/config/i386/t-crtfm b/gcc/config/i386/t-crtfm
index fc4b58784cad339b8f138e35b7975d86e7e8e066..f60eab52609819e0085576c01ba12f2368bc3586 100644
--- a/gcc/config/i386/t-crtfm
+++ b/gcc/config/i386/t-crtfm
@@ -1,6 +1,7 @@
 EXTRA_PARTS += crtfastmath.o
 
-$(T)crtfastmath.o: $(srcdir)/config/i386/crtfastmath.c $(GCC_PASSES)
-	$(GCC_FOR_TARGET) $(LIBGCC2_CFLAGS) -msse -c \
+$(T)crtfastmath.o: $(srcdir)/config/i386/crtfastmath.c \
+  $(srcdir)/config/i386/cpuid.h $(GCC_PASSES)
+	$(GCC_FOR_TARGET) $(LIBGCC2_CFLAGS) -msse -minline-all-stringops -c \
 		$(srcdir)/config/i386/crtfastmath.c \
 		-o $(T)crtfastmath$(objext)
diff --git a/gcc/config/i386/x-i386 b/gcc/config/i386/x-i386
index e156bcde3c961b07c41b38a42e284c428182bfc5..9f03de4535edbbf9fdee8cbff4eaf4952daf2b90 100644
--- a/gcc/config/i386/x-i386
+++ b/gcc/config/i386/x-i386
@@ -1,3 +1,4 @@
 driver-i386.o : $(srcdir)/config/i386/driver-i386.c \
+  $(srcdir)/config/i386/cpuid.h \
   $(CONFIG_H) $(SYSTEM_H) $(TM_H) coretypes.h
 	$(CC) -c $(ALL_CFLAGS) $(ALL_CPPFLAGS) $(INCLUDES) $<
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 2bb0865e7d95aba70c74135e66ab399f8210cda7..897d6a9f25e3dbb5faeeed954791e48285c6e028 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,23 @@
+2007-09-05  Uros Bizjak  <ubizjak@gmail.com>
+
+	* gcc.dg/i386-cpuid.h: Remove.
+	* gcc.target/i386/mmx-check.h: Include cpuid.h.
+	(main): Use __get_cpuid to get target features.
+	* gcc.target/i386/sse-check.h: Ditto.
+	* gcc.target/i386/sse2-check.h: Ditto.
+	* gcc.target/i386/sse3-check.h: Ditto.
+	* gcc.target/i386/ssse3-check.h: Ditto.
+	* gcc.target/i386/sse4_1-check.h: Ditto.
+	* gcc.target/i386/sse4_2-check.h: Ditto.
+	* gcc.target/i386/sse4a-check.h: Ditto.
+	* gcc.dg/torture/pr16104-1.c: Ditto.
+	(do_test): Change to void.
+	* gcc.target/i386/mmx-4.c: Do not use NOINLINE.
+	* gcc.target/i386/sse-6.c: Ditto.
+	* gcc.target/i386/sse-7.c: Ditto.
+	* g++.dg/other/i386-1.C: Include cpuid.h.
+	(main): New function.  Use __get_cpuid to get target fetaures.
+
 2007-09-05  Sandra Loosemore  <sandra@codesourcery.com>
 	    David Ung  <davidu@mips.com>
             Nigel Stephens <nigel@mips.com>
@@ -225,7 +245,8 @@
 	* gcc.dg/vect/vect-intfloat-conversion-4a.c: Mark functions noinline.
 	* gcc.dg/vect/vect-109.c: Mark functions noinline.
 	* gcc.dg/vect/no-scevccp-outer-22.c: Mark functions noinline.
-	* gcc.dg/vect/no-section-anchors-vect-outer-4h.c: Mark functions noinline.
+	* gcc.dg/vect/no-section-anchors-vect-outer-4h.c: Mark functions
+	noinline.
 	* gcc.dg/vect/vect-iv-3.c: Mark functions noinline.
 	* gcc.dg/vect/vect-reduc-pattern-2b.c: Mark functions noinline.
 	* gcc.dg/vect/vect-reduc-dot-s8a.c: Mark functions noinline.
@@ -361,15 +382,15 @@
 2007-09-04  Uros Bizjak  <ubizjak@gmail.com>
 
 	* gcc.target/i386/sse4a-check.h: New file.
-	* gcc.target/i386/sse4a-extract.c: Include sse4a-check.h. Remove main.
+	* gcc.target/i386/sse4a-extract.c: Include sse4a-check.h.  Remove main.
 	* gcc.target/i386/sse4a-insert.c: Ditto.
 	* gcc.target/i386/sse4a-montsd.c: Ditto.
 	* gcc.target/i386/sse4a-montss.c: Ditto.
 	* gcc.target/i386/mmx-check.h: New file.
-	* gcc.target/i386/mmx-4.c: Include mmx-check.h. Remove main.
+	* gcc.target/i386/mmx-4.c: Include mmx-check.h.  Remove main.
 	* gcc.target/i386/builtin-apply-mmx.c: Ditto.
 	* gcc.target/i386/sse-check.h: New file.
-	* gcc.target/i386/pr13685: Include sse-check.h. Remove main.
+	* gcc.target/i386/pr13685: Include sse-check.h.  Remove main.
 	* gcc.target/i386/sse-3.c: Ditto.
 	* gcc.target/i386/sse-7.c: Ditto.
 	* gcc.target/i386/sse-9.c: Ditto.
@@ -378,7 +399,7 @@
 	* gcc.target/i386/sse-recip-vec.c: Ditto.
 	* gcc.target/i386/20020523.c: Ditto. Rename from 20020523-2.c.
 	* gcc.target/i386/20020523-1.c: Remove.
-	* gcc.target/i386/sse2-lrint-vec.c: Include sse2-check.h. Remove main.
+	* gcc.target/i386/sse2-lrint-vec.c: Include sse2-check.h.  Remove main.
 	* gcc.target/i386/sse2-lrintf-vec.c: Ditto.
 	* gcc.target/i386/ssefn-4.c: Ditto.
 	* gcc.target/i386/sse-6.c: Ditto.
@@ -406,14 +427,11 @@
 
 2007-09-03  H.J. Lu  <hongjiu.lu@intel.com>
 
-	* gcc.dg/vect/no-tree-scev-cprop-vect-iv-1.c: Restored.  Moved
-	to ...
+	* gcc.dg/vect/no-tree-scev-cprop-vect-iv-1.c: Restored.  Moved to ...
 	* gcc.dg/vect/no-scevccp-vect-iv-1.c: New test.
-	* gcc.dg/vect/no-tree-scev-cprop-vect-iv-2.c: Restored.  Moved
-	to ...
+	* gcc.dg/vect/no-tree-scev-cprop-vect-iv-2.c: Restored.  Moved to ...
 	* gcc.dg/vect/no-scevccp-vect-iv-2.c: New test.
-	* gcc.dg/vect/no-tree-scev-cprop-vect-iv-3.c: Restored.  Moved
-	to ...
+	* gcc.dg/vect/no-tree-scev-cprop-vect-iv-3.c: Restored.  Moved to ...
 	* gcc.dg/vect/no-scevccp-vect-iv-3.c: New test.
 
 2007-09-03  Jesper Nilsson  <jesper.nilsson@axis.com>
diff --git a/gcc/testsuite/g++.dg/other/i386-1.C b/gcc/testsuite/g++.dg/other/i386-1.C
index 84e04f042b3e7f112461dda0513a5364e581c96f..853f913db1e9d3a0f7ee5474eb8a6b52152b7e13 100644
--- a/gcc/testsuite/g++.dg/other/i386-1.C
+++ b/gcc/testsuite/g++.dg/other/i386-1.C
@@ -1,10 +1,10 @@
 /* { dg-do run { target i?86-*-* x86_64-*-* } } */
 /* { dg-options "-msse2" } */
 
-#include "../../gcc.target/i386/sse2-check.h"
-
 #include <xmmintrin.h>
 
+#include "cpuid.h"
+
 static void
 sse2_test (void)
 {
@@ -20,3 +20,18 @@ sse2_test (void)
   if (r != 3.0f)
     abort ();
 }
+
+int
+main ()
+{
+  unsigned int eax, ebx, ecx, edx;
+ 
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
+    return 0;
+
+  /* Run SSE2 test only if host has SSE2 support.  */
+  if (edx & bit_SSE2)
+    sse2_test ();
+
+  return 0;
+}
diff --git a/gcc/testsuite/gcc.dg/i386-cpuid.h b/gcc/testsuite/gcc.dg/i386-cpuid.h
deleted file mode 100644
index 8c7a39f45a9c7dd64889d483106b8eea6693ec3f..0000000000000000000000000000000000000000
--- a/gcc/testsuite/gcc.dg/i386-cpuid.h
+++ /dev/null
@@ -1,152 +0,0 @@
-/* Helper file for i386 platform.  Runtime check for MMX/SSE/SSE2 support.
-   Used by 20020523-2.c and i386-sse-6.c, and possibly others.  */
-/* Plagarized from 20020523-2.c.  */
-
-/* %ecx */
-#define bit_SSE3 (1 << 0)
-#define bit_SSSE3 (1 << 9)
-#define bit_SSE4_1 (1 << 19)
-#define bit_SSE4_2 (1 << 20)
-#define bit_POPCNT (1 << 23)
-
-/* %edx */
-#define bit_CMOV (1 << 15)
-#define bit_MMX (1 << 23)
-#define bit_SSE (1 << 25)
-#define bit_SSE2 (1 << 26)
-
-/* Extended Features */
-/* %ecx */
-#define bit_SSE4a (1 << 6)
-
-#ifndef NOINLINE
-#define NOINLINE __attribute__ ((noinline))
-#endif
-
-static inline unsigned int
-i386_get_cpuid (unsigned int *ecx, unsigned int *edx)
-{
-  int fl1;
-
-#ifndef __x86_64__
-  int fl2;
-
-  /* See if we can use cpuid.  On AMD64 we always can.  */
-  __asm__ ("pushfl; pushfl; popl %0; movl %0,%1; xorl %2,%0;"
-	   "pushl %0; popfl; pushfl; popl %0; popfl"
-	   : "=&r" (fl1), "=&r" (fl2)
-	   : "i" (0x00200000));
-  if (((fl1 ^ fl2) & 0x00200000) == 0)
-    return (0);
-#endif
-
-  /* Host supports cpuid.  See if cpuid gives capabilities, try
-     CPUID(0).  Preserve %ebx and %ecx; cpuid insn clobbers these, we
-     don't need their CPUID values here, and %ebx may be the PIC
-     register.  */
-#ifdef __x86_64__
-  __asm__ ("pushq %%rcx; pushq %%rbx; cpuid; popq %%rbx; popq %%rcx"
-	   : "=a" (fl1) : "0" (0) : "rdx", "cc");
-#else
-  __asm__ ("pushl %%ecx; pushl %%ebx; cpuid; popl %%ebx; popl %%ecx"
-	   : "=a" (fl1) : "0" (0) : "edx", "cc");
-#endif
-  if (fl1 == 0)
-    return (0);
-
-  /* Invoke CPUID(1), return %ecx and %edx; caller can examine bits to
-     determine what's supported.  */
-#ifdef __x86_64__
-  __asm__ ("pushq %%rbx; cpuid; popq %%rbx"
-	   : "=c" (*ecx), "=d" (*edx), "=a" (fl1) : "2" (1) : "cc");
-#else
-  __asm__ ("pushl %%ebx; cpuid; popl %%ebx"
-	   : "=c" (*ecx), "=d" (*edx), "=a" (fl1) : "2" (1) : "cc");
-#endif
-
-  return 1;
-}
-
-static inline unsigned int
-i386_get_extended_cpuid (unsigned int *ecx, unsigned int *edx)
-{
-  int fl1;
-  if (!(i386_get_cpuid (ecx, edx)))
-    return 0;
-
-  /* Invoke CPUID(0x80000000) to get the highest supported extended function
-     number */
-#ifdef __x86_64__
-  __asm__ ("cpuid"
-	   : "=a" (fl1) : "0" (0x80000000) : "edx", "ecx", "ebx");
-#else
-  __asm__ ("pushl %%ebx; cpuid; popl %%ebx"
-	   : "=a" (fl1) : "0" (0x80000000) : "edx", "ecx");
-#endif
-  /* Check if highest supported extended function used below are supported */
-  if (fl1 < 0x80000001)
-    return 0;  
-
-  /* Invoke CPUID(0x80000001), return %ecx and %edx; caller can examine bits to
-     determine what's supported.  */
-#ifdef __x86_64__
-  __asm__ ("cpuid"
-	   : "=c" (*ecx), "=d" (*edx), "=a" (fl1) : "2" (0x80000001) : "ebx");
-#else
-  __asm__ ("pushl %%ebx; cpuid; popl %%ebx"
-	   : "=c" (*ecx), "=d" (*edx), "=a" (fl1) : "2" (0x80000001));
-#endif
-  return 1;
-}
-
-
-unsigned int i386_cpuid_ecx (void) NOINLINE;
-unsigned int i386_cpuid_edx (void) NOINLINE;
-unsigned int i386_extended_cpuid_ecx (void) NOINLINE;
-unsigned int i386_extended_cpuid_edx (void) NOINLINE;
-
-unsigned int NOINLINE
-i386_cpuid_ecx (void)
-{
-  unsigned int ecx, edx;
-  if (i386_get_cpuid (&ecx, &edx))
-    return ecx;
-  else
-    return 0;
-}
-
-unsigned int NOINLINE
-i386_cpuid_edx (void)
-{
-  unsigned int ecx, edx;
-  if (i386_get_cpuid (&ecx, &edx))
-    return edx;
-  else
-    return 0;
-}
-
-unsigned int NOINLINE
-i386_extended_cpuid_ecx (void)
-{
-  unsigned int ecx, edx;
-  if (i386_get_extended_cpuid (&ecx, &edx))
-    return ecx;
-  else
-    return 0;
-}
-
-unsigned int NOINLINE
-i386_extended_cpuid_edx (void)
-{
-  unsigned int ecx, edx;
-  if (i386_get_extended_cpuid (&ecx, &edx))
-    return edx;
-  else
-    return 0;
-}
-
-static inline unsigned int
-i386_cpuid (void)
-{
-  return i386_cpuid_edx ();
-}
diff --git a/gcc/testsuite/gcc.dg/torture/pr16104-1.c b/gcc/testsuite/gcc.dg/torture/pr16104-1.c
index 4cafbe718aa4f17ce6b7cb8ec9a67909f1942568..018a1bac7601e298965b5182421bc3cd6ebc871c 100644
--- a/gcc/testsuite/gcc.dg/torture/pr16104-1.c
+++ b/gcc/testsuite/gcc.dg/torture/pr16104-1.c
@@ -2,7 +2,7 @@
 /* { dg-do run { target i?86-*-* x86_64-*-* } } */
 /* { dg-options "-msse2" } */
 
-#include "../i386-cpuid.h"
+#include "cpuid.h"
 
 extern void abort (void);
 
@@ -41,12 +41,12 @@ test5 (V2USI x)
   return (V2SI) x;
 }
 
-int
+void
 __attribute__ ((noinline))
 do_test (void)
 {
   if (sizeof (short) != 2 || sizeof (int) != 4 || sizeof (long long) != 8)
-    return 0;
+    return;
 
   if (test1 () != 0)
     abort ();
@@ -70,19 +70,19 @@ do_test (void)
   u.x = test5 (z);
   if (u.y[0] != 6 || u.y[1] != 6)
     abort ();
-  return 0;
 }
 
 int
 main (void)
 {
-  unsigned long cpu_facilities;
-
-  cpu_facilities = i386_cpuid ();
-
-  if ((cpu_facilities & (bit_MMX | bit_SSE | bit_CMOV | bit_SSE2))
-      != (bit_MMX | bit_SSE | bit_CMOV | bit_SSE2))
+  unsigned int eax, ebx, ecx, edx;
+ 
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
     return 0;
 
-  return do_test ();
+  /* Run SSE2 test only if host has SSE2 support.  */
+  if (edx & bit_SSE2)
+    do_test ();
+
+  return 0;
 }
diff --git a/gcc/testsuite/gcc.target/i386/mmx-4.c b/gcc/testsuite/gcc.target/i386/mmx-4.c
index 297a76fe52619b58540a593191a2caf6ed2335c1..42c71f632d93103623ec0e8b5e95f094c542330d 100644
--- a/gcc/testsuite/gcc.target/i386/mmx-4.c
+++ b/gcc/testsuite/gcc.target/i386/mmx-4.c
@@ -16,7 +16,7 @@ typedef union {
   unsigned int u[2];
 }vecInWord;
 
-void mmx_tests (void) NOINLINE;
+void mmx_tests (void) __attribute__((noinline));
 void dump64_16 (char *, char *, vecInWord);
 void dump64_32 (char *, char *, vecInWord);
 void dump64_64 (char *, char *, vecInWord);
@@ -90,7 +90,7 @@ mmx_test (void)
     abort ();
 }
 
-void NOINLINE
+void __attribute__((noinline))
 mmx_tests (void)
 {
   /* psraw */
diff --git a/gcc/testsuite/gcc.target/i386/mmx-check.h b/gcc/testsuite/gcc.target/i386/mmx-check.h
index 0c6e1e9523be14485782e9753dd1ccb232e2e0a4..aefdc4e8799e4295b7abe3c378ea398e4ad2ab1e 100644
--- a/gcc/testsuite/gcc.target/i386/mmx-check.h
+++ b/gcc/testsuite/gcc.target/i386/mmx-check.h
@@ -1,20 +1,21 @@
 #include <stdio.h>
 #include <stdlib.h>
 
-#include "../../gcc.dg/i386-cpuid.h"
+#include "cpuid.h"
 
 static void mmx_test (void);
 
 int
 main ()
 {
-  unsigned long cpu_facilities;
+  unsigned int eax, ebx, ecx, edx;
  
-  cpu_facilities = i386_cpuid_edx ();
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
+    return 0;
 
   /* Run MMX test only if host has MMX support.  */
-  if ((cpu_facilities & bit_MMX))
+  if (edx & bit_MMX)
     mmx_test ();
 
-  exit (0);
+  return 0;
 }
diff --git a/gcc/testsuite/gcc.target/i386/sse-10.c b/gcc/testsuite/gcc.target/i386/sse-10.c
index 3116e80d3a9209d37e5eb1bd7e50b08ce859b56a..1c222df2b2f9a7af10da84151b457899b73aa132 100644
--- a/gcc/testsuite/gcc.target/i386/sse-10.c
+++ b/gcc/testsuite/gcc.target/i386/sse-10.c
@@ -6,7 +6,7 @@
 
 typedef _Complex double complex_16;
 
-void NOINLINE
+void __attribute__((noinline))
 test (complex_16 a[5][5])
 {
   int i, j, k;
diff --git a/gcc/testsuite/gcc.target/i386/sse-6.c b/gcc/testsuite/gcc.target/i386/sse-6.c
index 237a46372bc7ebdcb79aa694eebbd69d133874a9..f07a8cbc99bbb886e4ea1bfee763d5260aae0989 100644
--- a/gcc/testsuite/gcc.target/i386/sse-6.c
+++ b/gcc/testsuite/gcc.target/i386/sse-6.c
@@ -16,7 +16,7 @@ typedef union {
   unsigned char c[16];
 }vecInLong;
 
-void sse2_tests (void) NOINLINE;
+void sse2_tests (void) __attribute__((noinline));
 void dump128_16 (char *, char *, vecInLong);
 void dump128_32 (char *, char *, vecInLong);
 void dump128_64 (char *, char *, vecInLong);
@@ -110,7 +110,7 @@ sse2_test (void)
     abort ();
 }
 
-void NOINLINE
+void __attribute__((noinline))
 sse2_tests (void)
 {
   /* psraw */
diff --git a/gcc/testsuite/gcc.target/i386/sse-7.c b/gcc/testsuite/gcc.target/i386/sse-7.c
index 0ba0d65c63cae04d935bba88b5160f3ce36b056d..12b88ca53f3c01bbac22ce18794b1f0163fc0500 100644
--- a/gcc/testsuite/gcc.target/i386/sse-7.c
+++ b/gcc/testsuite/gcc.target/i386/sse-7.c
@@ -16,7 +16,7 @@ typedef union {
   unsigned int u[2];
 }vecInWord;
 
-void sse_tests (void) NOINLINE;
+void sse_tests (void) __attribute__((noinline));
 void dump64_16 (char *, char *, vecInWord);
 int check (const char *, const char *[]);
 
@@ -53,7 +53,7 @@ sse_test (void)
     abort ();
 }
 
-void NOINLINE
+void __attribute__((noinline))
 sse_tests (void)
 {
   /* pshufw */
diff --git a/gcc/testsuite/gcc.target/i386/sse-check.h b/gcc/testsuite/gcc.target/i386/sse-check.h
index 2fb14e61e0beb1a1034ea586e187b45891b51e33..d485b8dfa0390ab5859891a8e14990cbb6e01978 100644
--- a/gcc/testsuite/gcc.target/i386/sse-check.h
+++ b/gcc/testsuite/gcc.target/i386/sse-check.h
@@ -1,20 +1,21 @@
 #include <stdio.h>
 #include <stdlib.h>
 
-#include "../../gcc.dg/i386-cpuid.h"
+#include "cpuid.h"
 
 static void sse_test (void);
 
 int
 main ()
 {
-  unsigned long cpu_facilities;
+  unsigned int eax, ebx, ecx, edx;
  
-  cpu_facilities = i386_cpuid_edx ();
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
+    return 0;
 
   /* Run SSE test only if host has SSE support.  */
-  if ((cpu_facilities & bit_SSE))
+  if (edx & bit_SSE)
     sse_test ();
 
-  exit (0);
+  return 0;
 }
diff --git a/gcc/testsuite/gcc.target/i386/sse2-check.h b/gcc/testsuite/gcc.target/i386/sse2-check.h
index e6855136c6b71942992e6154c1cbaa23f5ebd01a..007ff543228791194c6cd795afa957f2151c05fc 100644
--- a/gcc/testsuite/gcc.target/i386/sse2-check.h
+++ b/gcc/testsuite/gcc.target/i386/sse2-check.h
@@ -1,20 +1,21 @@
 #include <stdio.h>
 #include <stdlib.h>
 
-#include "../../gcc.dg/i386-cpuid.h"
+#include "cpuid.h"
 
 static void sse2_test (void);
 
 int
 main ()
 {
-  unsigned long cpu_facilities;
+  unsigned int eax, ebx, ecx, edx;
  
-  cpu_facilities = i386_cpuid_edx ();
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
+    return 0;
 
   /* Run SSE2 test only if host has SSE2 support.  */
-  if ((cpu_facilities & bit_SSE2))
+  if (edx & bit_SSE2)
     sse2_test ();
 
-  exit (0);
+  return 0;
 }
diff --git a/gcc/testsuite/gcc.target/i386/sse3-check.h b/gcc/testsuite/gcc.target/i386/sse3-check.h
index 120c3e6e37508c4eb5b16869f58a740220ae9a12..92930d10a3fa8528c078ca7f41878a82cbac0698 100644
--- a/gcc/testsuite/gcc.target/i386/sse3-check.h
+++ b/gcc/testsuite/gcc.target/i386/sse3-check.h
@@ -1,19 +1,21 @@
+#include <stdio.h>
 #include <stdlib.h>
 
-#include "../../gcc.dg/i386-cpuid.h"
+#include "cpuid.h"
 
 static void sse3_test (void);
 
 int
 main ()
 {
-  unsigned long cpu_facilities;
+  unsigned int eax, ebx, ecx, edx;
+ 
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
+    return 0;
  
-  cpu_facilities = i386_cpuid_ecx ();
-
   /* Run SSE3 test only if host has SSE3 support.  */
-  if ((cpu_facilities & bit_SSE3))
+  if (ecx & bit_SSE3)
     sse3_test ();
 
-  exit (0);
+  return 0;
 }
diff --git a/gcc/testsuite/gcc.target/i386/sse4_1-check.h b/gcc/testsuite/gcc.target/i386/sse4_1-check.h
index 4bf9a84b4093cec25ceea2002df2719d3f63f54f..bac37cb56efa5dc50a03c1e1e120f9e217bf99aa 100644
--- a/gcc/testsuite/gcc.target/i386/sse4_1-check.h
+++ b/gcc/testsuite/gcc.target/i386/sse4_1-check.h
@@ -1,6 +1,7 @@
+#include <stdio.h>
 #include <stdlib.h>
 
-#include "../../gcc.dg/i386-cpuid.h"
+#include "cpuid.h"
 
 static void sse4_1_test (void);
 
@@ -9,13 +10,14 @@ static void sse4_1_test (void);
 int
 main ()
 {
-  unsigned long cpu_facilities;
+  unsigned int eax, ebx, ecx, edx;
  
-  cpu_facilities = i386_cpuid_ecx ();
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
+    return 0;
 
   /* Run SSE4.1 test only if host has SSE4.1 support.  */
-  if ((cpu_facilities & bit_SSE4_1))
+  if (ecx & bit_SSE4_1)
     sse4_1_test ();
 
-  exit (0);
+  return 0;
 }
diff --git a/gcc/testsuite/gcc.target/i386/sse4_2-check.h b/gcc/testsuite/gcc.target/i386/sse4_2-check.h
index 49bc0b308ab3642a7450646cb09b0a60dbbadb86..2a397e886834a03f8b65e7419f58c68d22cc504d 100644
--- a/gcc/testsuite/gcc.target/i386/sse4_2-check.h
+++ b/gcc/testsuite/gcc.target/i386/sse4_2-check.h
@@ -1,20 +1,21 @@
 #include <stdio.h>
 #include <stdlib.h>
 
-#include "../../gcc.dg/i386-cpuid.h"
+#include "cpuid.h"
 
 static void sse4_2_test (void);
 
 int
 main ()
 {
-  unsigned long cpu_facilities;
+  unsigned int eax, ebx, ecx, edx;
  
-  cpu_facilities = i386_cpuid_ecx ();
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
+    return 0;
 
   /* Run SSE4.2 test only if host has SSE4.2 support.  */
-  if ((cpu_facilities & bit_SSE4_2))
+  if (ecx & bit_SSE4_2)
     sse4_2_test ();
 
-  exit (0);
+  return 0;
 }
diff --git a/gcc/testsuite/gcc.target/i386/sse4a-check.h b/gcc/testsuite/gcc.target/i386/sse4a-check.h
index 388ce650f5f6432bee2e2340b9fa54e268c5e3e6..d6140e8969c94ee80f2ccb87124490a7da89221c 100644
--- a/gcc/testsuite/gcc.target/i386/sse4a-check.h
+++ b/gcc/testsuite/gcc.target/i386/sse4a-check.h
@@ -1,20 +1,21 @@
 #include <stdio.h>
 #include <stdlib.h>
 
-#include "../../gcc.dg/i386-cpuid.h"
+#include "cpuid.h"
 
 static void sse4a_test (void);
 
 int
 main ()
 {
-  unsigned long cpu_facilities;
+  unsigned int eax, ebx, ecx, edx;
  
-  cpu_facilities = i386_extended_cpuid_ecx ();
+  if (!__get_cpuid (0x80000001, &eax, &ebx, &ecx, &edx))
+    return 0;
 
   /* Run SSE4a test only if host has SSE4a support.  */
-  if ((cpu_facilities & bit_SSE4a))
+  if (ecx & bit_SSE4a)
     sse4a_test ();
 
-  exit (0);
+  return 0;
 }
diff --git a/gcc/testsuite/gcc.target/i386/ssse3-check.h b/gcc/testsuite/gcc.target/i386/ssse3-check.h
index 41f46f94ce90375cf18bc2ea1c838534b8813e00..78df15db7d74600deb42303746b9d0c725dc4097 100644
--- a/gcc/testsuite/gcc.target/i386/ssse3-check.h
+++ b/gcc/testsuite/gcc.target/i386/ssse3-check.h
@@ -1,19 +1,21 @@
+#include <stdio.h>
 #include <stdlib.h>
 
-#include "../../gcc.dg/i386-cpuid.h"
+#include "cpuid.h"
 
 static void ssse3_test (void);
 
 int
 main ()
 {
-  unsigned long cpu_facilities;
+  unsigned int eax, ebx, ecx, edx;
  
-  cpu_facilities = i386_cpuid_ecx ();
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
+    return 0;
 
   /* Run SSSE3 test only if host has SSSE3 support.  */
-  if ((cpu_facilities & bit_SSSE3))
+  if (ecx & bit_SSSE3)
     ssse3_test ();
 
-  exit (0);
+  return 0;
 }
diff --git a/libgomp/ChangeLog b/libgomp/ChangeLog
index 30959daea2395ca05e41a3096321b763c4827b26..90e40568dec60176d06c956bdfdaf32dc2bf91af 100644
--- a/libgomp/ChangeLog
+++ b/libgomp/ChangeLog
@@ -1,3 +1,10 @@
+2007-09-05  Uros Bizjak  <ubizjak@gmail.com>
+
+	* testsuite/libgomp.c/atomic-1.c: Include cpuid.h for i386 targets.
+	(main): Use __get_cpuid to get i386 target fetaures.
+	* testsuite/libgomp.c/atomic-2.c: Include cpuid.h for x86_64 targets.
+	(main): Use __get_cpuid to get x86_64 target fetaures.
+
 2007-08-15  Jack Howarth  <howarth@bromo.med.uc.edu>
 
 	PR target/32765
diff --git a/libgomp/testsuite/libgomp.c/atomic-1.c b/libgomp/testsuite/libgomp.c/atomic-1.c
index dfbcf851c44ce1adb1269fa91d6f703edf4a345e..b2be8f022ea11bba74e7c8d1133eb6940db9ba63 100644
--- a/libgomp/testsuite/libgomp.c/atomic-1.c
+++ b/libgomp/testsuite/libgomp.c/atomic-1.c
@@ -2,8 +2,7 @@
 /* { dg-options "-O2 -march=pentium" { target { { i?86-*-* x86_64-*-* } && ilp32 } } } */
 
 #ifdef __i386__
-#include "../../../gcc/testsuite/gcc.dg/i386-cpuid.h"
-#define bit_CX8 (1 << 8)
+#include "cpuid.h"
 #endif
 
 extern void abort (void);
@@ -41,11 +40,12 @@ int
 main (void)
 {
 #ifdef __i386__
-  unsigned long cpu_facilities;
+  unsigned int eax, ebx, ecx, edx;
 
-  cpu_facilities = i386_cpuid ();
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
+    return 0;
 
-  if (!(cpu_facilities & bit_CX8))
+  if (!(edx & bit_CMPXCHG8B))
     return 0;
 #endif
 
diff --git a/libgomp/testsuite/libgomp.c/atomic-2.c b/libgomp/testsuite/libgomp.c/atomic-2.c
index 50529ebe67528dfcd7482f4db7bf2a8657c28392..c8779483b816f078d39ed90ea855927e28af72da 100644
--- a/libgomp/testsuite/libgomp.c/atomic-2.c
+++ b/libgomp/testsuite/libgomp.c/atomic-2.c
@@ -1,6 +1,10 @@
 /* { dg-do run } */
 /* { dg-options "-O2 -mcx16" { target { { i?86-*-* x86_64-*-* } && lp64 } } } */
 
+#ifdef __x86_64__
+#include "cpuid.h"
+#endif
+
 double d = 1.5;
 long double ld = 3;
 extern void abort (void);
@@ -20,11 +24,12 @@ int
 main (void)
 {
 #ifdef __x86_64__
-# define bit_CX16 (1 << 13)
-  unsigned int ax, bx, cx, dx;
-  __asm__ ("cpuid" : "=a" (ax), "=b" (bx), "=c" (cx), "=d" (dx)
-           : "0" (1) : "cc");
-  if (!(cx & bit_CX16))
+  unsigned int eax, ebx, ecx, edx;
+
+  if (!__get_cpuid (1, &eax, &ebx, &ecx, &edx))
+    return 0;
+
+  if (!(ecx & bit_CMPXCHG16B))
     return 0;
 #endif
   test ();