diff --git a/libgfortran/ChangeLog b/libgfortran/ChangeLog
index d9d397bc1e0a1ce477c9f1e56e76a79d3e681876..b553031aad2e43160a3cd82dda157cd3248d4a4b 100644
--- a/libgfortran/ChangeLog
+++ b/libgfortran/ChangeLog
@@ -1,3 +1,23 @@
+2011-11-09  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR fortran/46686
+	* configure.ac: Don't check execinfo.h, backtrace,
+	backtrace_symbols_fd. Check execve instead of execvp. Call
+	GCC_CHECK_UNWIND_GETIPINFO.
+	* runtime/backtrace.c: Don't include unused headers, include
+	limits.h and unwind.h.
+	(CAN_FORK): Check execve instead of execvp.
+	(GLIBC_BACKTRACE): Remove.
+	(bt_header): Conform to gdb backtrace format.
+	(struct bt_state): New struct.
+	(trace_function): New function.
+	(show_backtrace): Use _Unwind_Backtrace from libgcc instead of
+	glibc backtrace functions.
+	* Makefile.in: Regenerated.
+	* aclocal.m4: Regenerated.
+	* config.h.in: Regenerated.
+	* configure: Regenerated.
+
 2011-11-09  Janne Blomqvist  <jb@gcc.gnu.org>
 
         PR libfortran/50016
diff --git a/libgfortran/Makefile.in b/libgfortran/Makefile.in
index 80a6c60968de5f19498158d9f0e3cf8451c0eda2..205037c7877ef015ba79178316d6e9907c62aae1 100644
--- a/libgfortran/Makefile.in
+++ b/libgfortran/Makefile.in
@@ -51,6 +51,7 @@ am__aclocal_m4_deps = $(top_srcdir)/../config/depstand.m4 \
 	$(top_srcdir)/../config/multi.m4 \
 	$(top_srcdir)/../config/override.m4 \
 	$(top_srcdir)/../config/stdint.m4 \
+	$(top_srcdir)/../config/unwind_ipinfo.m4 \
 	$(top_srcdir)/../ltoptions.m4 $(top_srcdir)/../ltsugar.m4 \
 	$(top_srcdir)/../ltversion.m4 $(top_srcdir)/../lt~obsolete.m4 \
 	$(top_srcdir)/acinclude.m4 $(top_srcdir)/../config/acx.m4 \
diff --git a/libgfortran/aclocal.m4 b/libgfortran/aclocal.m4
index cbac4af8f19dae891ca979e2e0d205faa1b86714..ebf36069e9a14f8b5d809ca85f84edf8d37ee91b 100644
--- a/libgfortran/aclocal.m4
+++ b/libgfortran/aclocal.m4
@@ -974,6 +974,7 @@ m4_include([../config/lthostflags.m4])
 m4_include([../config/multi.m4])
 m4_include([../config/override.m4])
 m4_include([../config/stdint.m4])
+m4_include([../config/unwind_ipinfo.m4])
 m4_include([../ltoptions.m4])
 m4_include([../ltsugar.m4])
 m4_include([../ltversion.m4])
diff --git a/libgfortran/config.h.in b/libgfortran/config.h.in
index 708ec7cd02dd55f9032e4628cdba4556e887efde..66d80665d9930c356ca119ef6b30106e46160546 100644
--- a/libgfortran/config.h.in
+++ b/libgfortran/config.h.in
@@ -81,12 +81,6 @@
 /* Define to 1 if the target supports __attribute__((visibility(...))). */
 #undef HAVE_ATTRIBUTE_VISIBILITY
 
-/* Define to 1 if you have the `backtrace' function. */
-#undef HAVE_BACKTRACE
-
-/* Define to 1 if you have the `backtrace_symbols_fd' function. */
-#undef HAVE_BACKTRACE_SYMBOLS_FD
-
 /* Define if powf is broken. */
 #undef HAVE_BROKEN_POWF
 
@@ -348,14 +342,11 @@
 /* libm includes erfl */
 #undef HAVE_ERFL
 
-/* Define to 1 if you have the <execinfo.h> header file. */
-#undef HAVE_EXECINFO_H
-
 /* Define to 1 if you have the `execl' function. */
 #undef HAVE_EXECL
 
-/* Define to 1 if you have the `execvp' function. */
-#undef HAVE_EXECVP
+/* Define to 1 if you have the `execve' function. */
+#undef HAVE_EXECVE
 
 /* libm includes exp */
 #undef HAVE_EXP
@@ -453,6 +444,9 @@
 /* Define to 1 if you have the `gethostname' function. */
 #undef HAVE_GETHOSTNAME
 
+/* Define if _Unwind_GetIPInfo is available. */
+#undef HAVE_GETIPINFO
+
 /* Define to 1 if you have the `getlogin' function. */
 #undef HAVE_GETLOGIN
 
diff --git a/libgfortran/configure b/libgfortran/configure
index 3a1174a1237ac7f8917e4e4b14b27776ce9d74c4..0ee67d5d1a7c1ef48bb9bb222f470826eb78a02a 100755
--- a/libgfortran/configure
+++ b/libgfortran/configure
@@ -766,6 +766,7 @@ with_gnu_ld
 enable_libtool_lock
 enable_largefile
 enable_libquadmath_support
+with_system_libunwind
 '
       ac_precious_vars='build_alias
 host_alias
@@ -1424,6 +1425,7 @@ Optional Packages:
   --with-pic              try to use only PIC/non-PIC objects [default=use
                           both]
   --with-gnu-ld           assume the C compiler uses GNU ld [default=no]
+  --with-system-libunwind use installed libunwind
 
 Some influential environment variables:
   CC          C compiler command
@@ -12112,7 +12114,7 @@ else
   lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2
   lt_status=$lt_dlunknown
   cat > conftest.$ac_ext <<_LT_EOF
-#line 12115 "configure"
+#line 12117 "configure"
 #include "confdefs.h"
 
 #if HAVE_DLFCN_H
@@ -12218,7 +12220,7 @@ else
   lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2
   lt_status=$lt_dlunknown
   cat > conftest.$ac_ext <<_LT_EOF
-#line 12221 "configure"
+#line 12223 "configure"
 #include "confdefs.h"
 
 #if HAVE_DLFCN_H
@@ -15919,7 +15921,7 @@ fi
 
 done
 
-for ac_header in fenv.h fptrap.h float.h execinfo.h pwd.h
+for ac_header in fenv.h fptrap.h float.h pwd.h
 do :
   as_ac_Header=`$as_echo "ac_cv_header_$ac_header" | $as_tr_sh`
 ac_fn_c_check_header_mongrel "$LINENO" "$ac_header" "$as_ac_Header" "$ac_includes_default"
@@ -16419,7 +16421,7 @@ _ACEOF
 fi
 done
 
-for ac_func in wait setmode execvp pipe dup2 close fdopen strcasestr getrlimit
+for ac_func in wait setmode execve pipe dup2 close fdopen strcasestr getrlimit
 do :
   as_ac_var=`$as_echo "ac_cv_func_$ac_func" | $as_tr_sh`
 ac_fn_c_check_func "$LINENO" "$ac_func" "$as_ac_var"
@@ -16472,21 +16474,6 @@ fi
 done
 
 
-# Check for glibc backtrace functions
-for ac_func in backtrace backtrace_symbols_fd
-do :
-  as_ac_var=`$as_echo "ac_cv_func_$ac_func" | $as_tr_sh`
-ac_fn_c_check_func "$LINENO" "$ac_func" "$as_ac_var"
-eval as_val=\$$as_ac_var
-   if test "x$as_val" = x""yes; then :
-  cat >>confdefs.h <<_ACEOF
-#define `$as_echo "HAVE_$ac_func" | $as_tr_cpp` 1
-_ACEOF
-
-fi
-done
-
-
 # Check libc for getgid, getpid, getuid
 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for getgid in -lc" >&5
 $as_echo_n "checking for getgid in -lc... " >&6; }
@@ -25880,6 +25867,44 @@ $as_echo "#define HAVE_CRLF 1" >>confdefs.h
 
 fi
 
+# Check whether we have _Unwind_GetIPInfo for backtrace
+
+
+# Check whether --with-system-libunwind was given.
+if test "${with_system_libunwind+set}" = set; then :
+  withval=$with_system_libunwind;
+fi
+
+  # If system-libunwind was not specifically set, pick a default setting.
+  if test x$with_system_libunwind = x; then
+    case ${target} in
+      ia64-*-hpux*) with_system_libunwind=yes ;;
+      *) with_system_libunwind=no ;;
+    esac
+  fi
+  # Based on system-libunwind and target, do we have ipinfo?
+  if  test x$with_system_libunwind = xyes; then
+    case ${target} in
+      ia64-*-*) have_unwind_getipinfo=no ;;
+      *) have_unwind_getipinfo=yes ;;
+    esac
+  else
+    # Darwin before version 9 does not have _Unwind_GetIPInfo.
+
+    case ${target} in
+      *-*-darwin[3-8]|*-*-darwin[3-8].*) have_unwind_getipinfo=no ;;
+      *) have_unwind_getipinfo=yes ;;
+    esac
+
+  fi
+
+  if test x$have_unwind_getipinfo = xyes; then
+
+$as_echo "#define HAVE_GETIPINFO 1" >>confdefs.h
+
+  fi
+
+
 cat >confcache <<\_ACEOF
 # This file is a shell script that caches the results of configure
 # tests run on this system so they can be shared between configure
diff --git a/libgfortran/configure.ac b/libgfortran/configure.ac
index 447ea9df998e4b073ea6e92233cc11c2cfcb614e..dbad8f5b16d40b4d23fc36562b1097e0fd45be84 100644
--- a/libgfortran/configure.ac
+++ b/libgfortran/configure.ac
@@ -249,7 +249,7 @@ AC_HEADER_TIME
 AC_HAVE_HEADERS(stdio.h stdlib.h string.h unistd.h signal.h stdarg.h)
 AC_CHECK_HEADERS(time.h sys/time.h sys/times.h sys/resource.h)
 AC_CHECK_HEADERS(sys/types.h sys/stat.h sys/wait.h floatingpoint.h ieeefp.h)
-AC_CHECK_HEADERS(fenv.h fptrap.h float.h execinfo.h pwd.h)
+AC_CHECK_HEADERS(fenv.h fptrap.h float.h pwd.h)
 AC_CHECK_HEADER([complex.h],[AC_DEFINE([HAVE_COMPLEX_H], [1], [complex.h exists])])
 GCC_HEADER_STDINT(gstdint.h)
 
@@ -261,14 +261,11 @@ AC_CHECK_MEMBERS([struct stat.st_rdev])
 AC_CHECK_FUNCS(getrusage times mkstemp strtof strtold snprintf ftruncate chsize)
 AC_CHECK_FUNCS(chdir strerror getlogin gethostname kill link symlink perror)
 AC_CHECK_FUNCS(sleep time ttyname signal alarm clock access fork execl)
-AC_CHECK_FUNCS(wait setmode execvp pipe dup2 close fdopen strcasestr getrlimit)
+AC_CHECK_FUNCS(wait setmode execve pipe dup2 close fdopen strcasestr getrlimit)
 AC_CHECK_FUNCS(gettimeofday stat fstat lstat getpwuid vsnprintf dup getcwd)
 AC_CHECK_FUNCS(localtime_r gmtime_r strerror_r getpwuid_r ttyname_r)
 AC_CHECK_FUNCS(clock_gettime strftime readlink)
 
-# Check for glibc backtrace functions
-AC_CHECK_FUNCS(backtrace backtrace_symbols_fd)
-
 # Check libc for getgid, getpid, getuid
 AC_CHECK_LIB([c],[getgid],[AC_DEFINE([HAVE_GETGID],[1],[libc includes getgid])])
 AC_CHECK_LIB([c],[getpid],[AC_DEFINE([HAVE_GETPID],[1],[libc includes getpid])])
@@ -559,6 +556,9 @@ LIBGFOR_CHECK_UNLINK_OPEN_FILE
 # Check whether line terminator is LF or CRLF
 LIBGFOR_CHECK_CRLF
 
+# Check whether we have _Unwind_GetIPInfo for backtrace
+GCC_CHECK_UNWIND_GETIPINFO
+
 AC_CACHE_SAVE
 
 if test ${multilib} = yes; then
diff --git a/libgfortran/runtime/backtrace.c b/libgfortran/runtime/backtrace.c
index 7d6479fe9055bf1bd99c8bb12d4bbb034b6f4fd8..70aae91cfe99f2ffefb1368be4a21dc7bbee50c4 100644
--- a/libgfortran/runtime/backtrace.c
+++ b/libgfortran/runtime/backtrace.c
@@ -26,46 +26,38 @@ see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
 
 #include <string.h>
 
-#ifdef HAVE_STDLIB_H
-#include <stdlib.h>
-#endif
-
-#ifdef HAVE_INTTYPES_H
-#include <inttypes.h>
-#endif
-
 #ifdef HAVE_UNISTD_H
 #include <unistd.h>
 #endif
 
-#ifdef HAVE_EXECINFO_H
-#include <execinfo.h>
-#endif
-
 #ifdef HAVE_SYS_WAIT_H
 #include <sys/wait.h>
 #endif
 
-#include <ctype.h>
+#include <limits.h>
+
+#include "unwind.h"
 
 
 /* Macros for common sets of capabilities: can we fork and exec, can
    we use glibc-style backtrace functions, and can we use pipes.  */
-#define CAN_FORK (defined(HAVE_FORK) && defined(HAVE_EXECVP) \
+#define CAN_FORK (defined(HAVE_FORK) && defined(HAVE_EXECVE) \
 		  && defined(HAVE_WAIT))
-#define GLIBC_BACKTRACE (defined(HAVE_BACKTRACE) \
-			 && defined(HAVE_BACKTRACE_SYMBOLS_FD))
 #define CAN_PIPE (CAN_FORK && defined(HAVE_PIPE) \
 		  && defined(HAVE_DUP2) && defined(HAVE_FDOPEN) \
 		  && defined(HAVE_CLOSE))
 
+#ifndef PATH_MAX
+#define PATH_MAX 4096
+#endif
+
 
 /* GDB style #NUM index for each stack frame.  */
 
 static void 
 bt_header (int num)
 {
-  st_printf (" #%d  ", num);
+  st_printf ("#%d  ", num);
 }
 
 
@@ -106,24 +98,105 @@ fd_gets (char *s, int size, int fd)
 
 extern char *addr2line_path;
 
+/* Struct containing backtrace state.  */
+typedef struct
+{
+  int frame_number;
+  int direct_output;
+  int outfd;
+  int infd;
+  int error;
+}
+bt_state;
 
-/* show_backtrace displays the backtrace, currently obtained by means of
-   the glibc backtrace* functions.  */
+static _Unwind_Reason_Code
+trace_function (struct _Unwind_Context *context, void *state_ptr)
+{
+  bt_state* state = (bt_state*) state_ptr;
+  _Unwind_Ptr ip;
+#ifdef HAVE_GETIPINFO
+  int ip_before_insn = 0;
+  ip = _Unwind_GetIPInfo (context, &ip_before_insn);
+  
+  /* If the unwinder gave us a 'return' address, roll it back a little
+     to ensure we get the correct line number for the call itself.  */
+  if (! ip_before_insn)
+    --ip;
+#else  
+  ip = _Unwind_GetIP (context);
+#endif
+
+  if (state->direct_output)
+    {
+      bt_header(state->frame_number);
+      st_printf ("%p\n", (void*) ip);
+    }
+  else
+    {
+      char addr_buf[GFC_XTOA_BUF_SIZE], func[1024], file[PATH_MAX];
+      char *p;
+      const char* addr = gfc_xtoa (ip, addr_buf, sizeof (addr_buf));
+      write (state->outfd, addr, strlen (addr));
+      write (state->outfd, "\n", 1);
+
+      if (! fd_gets (func, sizeof(func), state->infd))
+	{
+	  state->error = 1;
+	  goto done;
+	}
+      if (! fd_gets (file, sizeof(file), state->infd))
+	{
+	  state->error = 1;
+	  goto done;
+	}
+	    
+	for (p = func; *p != '\n' && *p != '\r'; p++)
+	  ;
+	*p = '\0';
+	
+	/* _start is a setup routine that calls main(), and main() is
+	   the frontend routine that calls some setup stuff and then
+	   calls MAIN__, so at this point we should stop.  */
+	if (strcmp (func, "_start") == 0 || strcmp (func, "main") == 0)
+	  return _URC_END_OF_STACK;
+	
+	bt_header (state->frame_number);
+	estr_write ("0x");
+	estr_write (addr);
+
+	if (func[0] != '?' && func[1] != '?')
+	  {
+	    estr_write (" in ");
+	    estr_write (func);
+	  }
+	
+	if (strncmp (file, "??", 2) == 0)
+	  estr_write ("\n");
+	else
+	  {
+	    estr_write (" at ");
+	    estr_write (file);
+	  }
+    }
+
+ done:
+
+  state->frame_number++;
+  
+  return _URC_NO_REASON;
+}
+
+
+/* Display the backtrace.  */
 
 void
 show_backtrace (void)
 {
-#if GLIBC_BACKTRACE
+  bt_state state;
+  state.frame_number = 0;
+  state.error = 0;
 
-#define DEPTH 50
-#define BUFSIZE 1024
-
-  void *trace[DEPTH];
-  int depth;
-
-  depth = backtrace (trace, DEPTH);
-  if (depth <= 0)
-    return;
+  estr_write ("\nA fatal error occurred! Backtrace for this error:\n");
 
 #if CAN_PIPE
 
@@ -134,9 +207,7 @@ show_backtrace (void)
   do
   {
     /* Local variables.  */
-    int f[2], pid, bt[2], inp[2];
-    char addr_buf[GFC_XTOA_BUF_SIZE], func[BUFSIZE], file[BUFSIZE];
-    char *p;
+    int f[2], pid, inp[2];
 
     /* Don't output an error message if something goes wrong, we'll simply
        fall back to the pstack and glibc backtraces.  */
@@ -182,139 +253,27 @@ show_backtrace (void)
     /* Father process.  */
     close (f[1]);
     close (inp[0]);
-    if (pipe (bt) != 0)
-      break;
-    backtrace_symbols_fd (trace, depth, bt[1]);
-    close (bt[1]);
-
-    estr_write ("\nBacktrace for this error:\n");
-    for (int j = 0; j < depth; j++)
-      {
-	const char *addr = gfc_xtoa 
-	  ((GFC_UINTEGER_LARGEST) (intptr_t) trace[j], 
-	   addr_buf, sizeof (addr_buf));
-
-	write (inp[1], addr, strlen (addr));
-	write (inp[1], "\n", 1);
-	
-	if (! fd_gets (func, sizeof(func), f[0]))
-	  goto fallback;
-	if (! fd_gets (file, sizeof(file), f[0]))
-	  goto fallback;
-	    
-	for (p = func; *p != '\n' && *p != '\r'; p++)
-	  ;
-	*p = '\0';
-	
-	/* If we only have the address, use the glibc backtrace.  */
-	if (func[0] == '?' && func[1] == '?' && file[0] == '?'
-	    && file[1] == '?')
-	  {
-	    bt_header (j);
-	    while (1)
-	      {
-		char bc;
-		ssize_t nread = read (bt[0], &bc, 1);
-		if (nread != 1 || bc == '\n')
-		  break;
-		write (STDERR_FILENO, &bc, 1);
-	      }
-	    estr_write ("\n");
-	    continue;
-	  }
-	else
-	  {
-	    /* Forward to the next entry in the backtrace. */
-	    while (1)
-	      {
-		char bc;
-		ssize_t nread = read (bt[0], &bc, 1);
-		if (nread != 1 || bc == '\n')
-		  break;
-	      }
-	  }
 
-	/* _start is a setup routine that calls main(), and main() is
-	   the frontend routine that calls some setup stuff and then
-	   calls MAIN__, so at this point we should stop.  */
-	if (strcmp (func, "_start") == 0 || strcmp (func, "main") == 0)
-	  break;
-	
-	bt_header (j);
-	estr_write (full_exe_path ());
-	estr_write ("[0x");
-	estr_write (addr);
-	estr_write ("] in ");
-	estr_write (func);
-	
-	if (strncmp (file, "??", 2) == 0)
-	  estr_write ("\n");
-	else
-	  {
-	    estr_write (" at ");
-	    estr_write (file);
-	  }
-      } /* Loop over each hex address.  */
+    state.outfd = inp[1];
+    state.infd = f[0];
+    state.direct_output = 0;
+    _Unwind_Backtrace (trace_function, &state);
+    if (state.error)
+      goto fallback;
     close (inp[1]);
-    close (bt[0]);
     wait (NULL);
     return;
 
 fallback:
     estr_write ("** Something went wrong while running addr2line. **\n"
-		"** Falling back  to a simpler  backtrace scheme. **\n");
+		"** Falling back to a simpler backtrace scheme. **\n");
   }
   while (0);
 
-#undef DEPTH
-#undef BUFSIZE
-
 #endif /* CAN_PIPE */
 
 fallback_noerr:
-  /* Fallback to the glibc backtrace.  */
-  estr_write ("\nBacktrace for this error:\n");
-  backtrace_symbols_fd (trace, depth, STDERR_FILENO);
-  return;
-
-#elif defined(CAN_FORK) && defined(HAVE_GETPPID)
-  /* Try to call pstack.  */
-  do
-  {
-    /* Local variables.  */
-    int pid;
-
-    /* Don't output an error message if something goes wrong, we'll simply
-       fall back to the pstack and glibc backtraces.  */
-    if ((pid = fork ()) == -1)
-      break;
-
-    if (pid == 0)
-      {
-	/* Child process.  */
-#define NUM_ARGS 2
-	char *arg[NUM_ARGS+1];
-	char buf[20];
-
-	estr_write ("\nBacktrace for this error:\n");
-	arg[0] = (char *) "pstack";
-	snprintf (buf, sizeof(buf), "%d", (int) getppid ());
-	arg[1] = buf;
-	arg[2] = NULL;
-	execvp (arg[0], arg);
-#undef NUM_ARGS
-
-	/* pstack didn't work.  */
-	estr_write ("  unable to produce a backtrace, sorry!\n");
-	_exit (1);
-      }
-
-    /* Father process.  */
-    wait (NULL);
-    return;
-  }
-  while(0);
-#else
-  estr_write ("\nBacktrace not yet available on this platform, sorry!\n");
-#endif
+  /* Fallback to the simple backtrace without addr2line.  */
+  state.direct_output = 1;
+  _Unwind_Backtrace (trace_function, &state);
 }