Index: erts/configure
--- erts/configure.orig	2009-09-21 11:29:49 +0200
+++ erts/configure	2009-09-23 20:39:09 +0200
@@ -11331,7 +11331,7 @@
 
 
 
-if test "x$enable_sctp" == "xyes" ; then
+if test "x$enable_sctp" = "xyes" ; then
     echo "$as_me:$LINENO: checking for netinet/sctp.h" >&5
 echo $ECHO_N "checking for netinet/sctp.h... $ECHO_C" >&6
 if test "${ac_cv_header_netinet_sctp_h+set}" = set; then
Index: erts/emulator/Makefile.in
--- erts/emulator/Makefile.in.orig	2009-09-18 16:06:45 +0200
+++ erts/emulator/Makefile.in	2009-09-23 20:39:09 +0200
@@ -611,7 +611,7 @@
 
 
 $(OBJDIR)/%.o: beam/%.c
-	$(CC) $(subst -O2, $(GEN_OPT_FLGS), $(CFLAGS)) $(INCLUDES) -c $< -o $@
+	$(CC) $(INCLUDES) $(subst -O2, $(GEN_OPT_FLGS), $(CFLAGS)) -c $< -o $@
 
 else
 
Index: erts/emulator/beam/erl_time_sup.c
--- erts/emulator/beam/erl_time_sup.c.orig	2009-06-05 14:53:17 +0200
+++ erts/emulator/beam/erl_time_sup.c	2009-09-23 20:39:09 +0200
@@ -650,6 +650,9 @@
     t.tm_sec = *second;
     t.tm_isdst = isdst;
     the_clock = mktime(&t);
+    if (the_clock == -1) {
+      return 0;
+    }
 #ifdef HAVE_GMTIME_R
     gmtime_r(&the_clock, (tm = &tmbuf));
 #else
Index: erts/emulator/drivers/common/inet_drv.c
--- erts/emulator/drivers/common/inet_drv.c.orig	2009-06-05 14:53:08 +0200
+++ erts/emulator/drivers/common/inet_drv.c	2009-09-23 20:39:09 +0200
@@ -5305,12 +5305,15 @@
 	    if (pmtud_enable)			cflags |= SPP_PMTUD_ENABLE;
 	    if (pmtud_disable)			cflags |= SPP_PMTUD_DISABLE;
 
+#	    ifdef HAVE_STRUCT_SCTP_PADDRPARAMS_SPP_SACKDELAY
+	    /* The followings are missing in FreeBSD 7.1 */
 	    sackdelay_enable =eflags& SCTP_FLAG_SACDELAY_ENABLE;
 	    sackdelay_disable=eflags& SCTP_FLAG_SACDELAY_DISABLE;
 	    if (sackdelay_enable && sackdelay_disable)
 		return -1;
 	    if (sackdelay_enable)		cflags |= SPP_SACKDELAY_ENABLE;
 	    if (sackdelay_disable)		cflags |= SPP_SACKDELAY_DISABLE;
+#           endif
 
 	    arg.pap.spp_flags  = cflags;
 #	    endif
@@ -6211,13 +6214,15 @@
 	    
 	    if (ap.spp_flags & SPP_PMTUD_DISABLE)
 		{ i = LOAD_ATOM (spec, i, am_pmtud_disable);         n++; }
-	    
+#	    ifdef HAVE_STRUCT_SCTP_PADDRPARAMS_SPP_SACKDELAY
+	    /* SPP_SACKDELAY_* not in FreeBSD 7.1 */
 	    if (ap.spp_flags & SPP_SACKDELAY_ENABLE)
 		{ i = LOAD_ATOM (spec, i, am_sackdelay_enable);      n++; }
 	    
 	    if (ap.spp_flags & SPP_SACKDELAY_DISABLE)
 		{ i = LOAD_ATOM (spec, i, am_sackdelay_disable);     n++; }
 #	    endif
+#	    endif
 	    
 	    PLACE_FOR(spec, i,
 		      LOAD_NIL_CNT + LOAD_LIST_CNT + 2*LOAD_TUPLE_CNT);
Index: erts/emulator/hipe/hipe_x86.c
--- erts/emulator/hipe/hipe_x86.c.orig	2009-03-12 13:16:21 +0100
+++ erts/emulator/hipe/hipe_x86.c	2009-09-23 20:39:09 +0200
@@ -130,7 +130,7 @@
 	abort();
     map_start = mmap(map_hint, map_bytes,
 		     PROT_EXEC|PROT_READ|PROT_WRITE,
-		     MAP_PRIVATE|MAP_ANONYMOUS
+		     MAP_PRIVATE|MAP_ANON
 #ifdef __x86_64__
 		     |MAP_32BIT
 #endif
Index: erts/etc/unix/Install.src
--- erts/etc/unix/Install.src.orig	2009-09-18 16:07:12 +0200
+++ erts/etc/unix/Install.src	2009-09-23 20:39:09 +0200
@@ -172,4 +172,4 @@
     ./misc/format_man_pages $ERL_ROOT
 fi
 
-
+exit 0
Index: lib/asn1/c_src/Makefile.in
--- lib/asn1/c_src/Makefile.in.orig	2009-09-18 16:10:43 +0200
+++ lib/asn1/c_src/Makefile.in	2009-09-23 20:39:09 +0200
@@ -114,7 +114,7 @@
 	$(CC) -c $(CFLAGS) -o $(OBJ_FILES) $(C_FILES) 
 
 $(SHARED_OBJ_FILES): $(OBJ_FILES) $(LIBDIR)
-	$(LD) $(LDFLAGS) $(LD_INCL_EI) -o $(SHARED_OBJ_FILES) $(OBJ_FILES) $(LD_EI) $(CLIB_FLAGS) $(LIBS) 
+	$(LD) $(LDFLAGS) $(LD_INCL_EI) -o $(SHARED_OBJ_FILES) $(OBJ_FILES) $(LD_EI)
 
 $(LIBDIR):
 	-mkdir -p $(LIBDIR)
Index: lib/crypto/c_src/Makefile.in
--- lib/crypto/c_src/Makefile.in.orig	2009-09-18 16:12:32 +0200
+++ lib/crypto/c_src/Makefile.in	2009-09-23 20:39:09 +0200
@@ -136,7 +136,7 @@
 release_spec: opt
 	$(INSTALL_DIR) $(RELSYSDIR)/priv/obj
 	$(INSTALL_DIR) $(RELSYSDIR)/priv/lib
-	$(INSTALL_PROGRAM) $(DRV_MAKEFILE) $(RELSYSDIR)/priv/obj
+	$(INSTALL_DATA) $(DRV_MAKEFILE) $(RELSYSDIR)/priv/obj
 	$(INSTALL_PROGRAM) $(OBJS) $(RELSYSDIR)/priv/obj
 	$(INSTALL_PROGRAM) $(DYN_DRIVER) $(RELSYSDIR)/priv/lib
 
Index: lib/erl_interface/src/connect/ei_resolve.c
--- lib/erl_interface/src/connect/ei_resolve.c.orig	2009-03-12 13:19:12 +0100
+++ lib/erl_interface/src/connect/ei_resolve.c	2009-09-23 20:39:09 +0200
@@ -54,6 +54,10 @@
 #include "ei_resolve.h"
 #include "ei_locking.h"
 
+#if defined(HAVE_GETHOSTBYNAME_R) && defined(__FreeBSD__)
+#undef HAVE_GETHOSTBYNAME_R
+#endif
+
 #ifdef HAVE_GETHOSTBYNAME_R
 
 void ei_init_resolve(void)
Index: lib/et/src/et_contents_viewer.erl
--- lib/et/src/et_contents_viewer.erl.orig	2009-03-13 12:11:21 +0100
+++ lib/et/src/et_contents_viewer.erl	2009-09-23 20:39:09 +0200
@@ -347,7 +347,6 @@
         'Caps_Lock' ->
             {noreply, S};
         _ ->
-            io:format("~p: ignored: ~p~n", [?MODULE, KeySym]),
             {noreply, S}
     end;
 handle_info({gs, _Obj, configure, [], [W, H | _]}, S) ->
Index: lib/et/src/et_viewer.erl
--- lib/et/src/et_viewer.erl.orig	2009-03-13 12:11:22 +0100
+++ lib/et/src/et_viewer.erl	2009-09-23 20:39:09 +0200
@@ -976,8 +976,7 @@
     noreply(S).
 
 click_error(Click, S) ->
-    gs:config(S#state.canvas, beep),
-    io:format("~p: ignored: ~p~n", [?MODULE, Click]).
+    gs:config(S#state.canvas, beep).
 
 %%%----------------------------------------------------------------------
 %%% Clone viewer
Index: lib/gs/src/tool_utils.erl
--- lib/gs/src/tool_utils.erl.orig	2009-03-12 13:23:23 +0100
+++ lib/gs/src/tool_utils.erl	2009-09-23 20:39:09 +0200
@@ -40,6 +40,9 @@
 	       }).
 
 
+%% Browser executable list (openURL command line protocol required)
+-define(BROWSERS, ["netscape", "mozilla", "MozillaFirebird", "opera", "firefox", "seamonkey"]).
+
 %%----------------------------------------------------------------------
 %% open_help(Parent, File)
 %%   Parent = gsobj()  (GS root object or parent window)
@@ -80,7 +83,7 @@
 		      {unix,Type} ->
                           case Type of
                                darwin -> "open " ++ File;
-                               _Else -> "netscape -remote \"openURL(file:" ++ File ++ ")\""
+                               _Else -> unix_url_command("file:" ++ File)
 			  end;
 		      {win32,_AnyType} ->
 			  "start " ++ filename:nativename(File);
@@ -95,7 +98,7 @@
 		      {unix,Type} ->
                           case Type of
                                darwin -> "open " ++ File;
-                               _Else -> "netscape -remote \"openURL(file:" ++ File ++ ")\""
+                               _Else -> unix_url_command("file:" ++ File)
 			  end;
 		      {win32,_AnyType} ->
 			  "netscape.exe -h " ++ regexp:gsub(File,"\\\\","/");
@@ -432,3 +435,53 @@
     [Last];
 insert_newlines(Other) ->
     Other.
+
+%% find_browser(BrowserList) => string() | false
+%%   BrowserList - [string()]
+%% Given a list of basenames, find the first available executable.
+
+find_browser([]) ->
+    false;
+
+find_browser([H | T]) ->
+    case os:find_executable(H) of
+        false ->
+          find_browser(T);
+        Browser ->
+          Browser
+    end.
+
+%% unix_url_command(URL) => string()
+%%   URL - string()
+%% Open an URL, using a browser which supports the openURL command
+%% line protocol. If no browser is found, the empty string will be
+%% returned.
+
+unix_url_command(URL) ->
+    Template = "BROWSER -remote \"openURL(" ++ URL ++ ")\" || BROWSER " ++ URL ++ "&",
+
+    case os:getenv("BROWSER") of
+	false ->
+	    %% look for a compatible browser
+	    case find_browser(?BROWSERS) of
+		false ->
+		    "";
+		Browser ->
+		    case regexp:gsub(Template, "BROWSER", Browser) of
+			{ok, Command, 0} ->
+			    %% Template does not contain "BROWSER" placeholder
+			    "";
+			{ok, Command, _} ->
+			    Command
+		    end
+	    end;
+
+	Value ->
+	    case regexp:gsub(Template, "BROWSER", Value) of
+		{ok, Command2, 0} ->
+		    %% no placeholder
+		    "";
+		{ok, Command2, _} ->
+		    Command2
+	    end
+    end.
Index: lib/hipe/regalloc/Makefile
--- lib/hipe/regalloc/Makefile.orig	2009-04-16 11:24:04 +0200
+++ lib/hipe/regalloc/Makefile	2009-09-23 20:39:09 +0200
@@ -46,7 +46,6 @@
 	  hipe_node_sets hipe_spillcost hipe_reg_worklists \
 	  hipe_adj_list \
 	  hipe_temp_map \
-	  hipe_optimistic_regalloc \
 	  hipe_coalescing_regalloc \
 	  hipe_graph_coloring_regalloc \
 	  hipe_regalloc_loop \
Index: lib/inets/src/http_client/http.erl
--- lib/inets/src/http_client/http.erl.orig	2009-09-18 14:47:45 +0200
+++ lib/inets/src/http_client/http.erl	2009-09-23 20:39:09 +0200
@@ -292,6 +292,8 @@
     case {Sync, Stream} of
 	{true, self} ->
 	    {error, streaming_error};
+	{true, {self,once}} ->
+	    {error, streaming_error};
 	_ ->
 	    RecordHeaders = header_record(NewHeaders, 
 					  #http_request_h{}, 
Index: lib/odbc/c_src/odbcserver.c
--- lib/odbc/c_src/odbcserver.c.orig	2009-06-05 14:55:24 +0200
+++ lib/odbc/c_src/odbcserver.c	2009-09-23 20:39:09 +0200
@@ -119,6 +119,7 @@
 #include <sys/socket.h>
 #include <sys/uio.h>
 #include <netdb.h>
+#include <netinet/in.h>
 #endif
 
 #include <limits.h>
Index: lib/sasl/src/rb.erl
--- lib/sasl/src/rb.erl.orig	2009-03-12 13:18:20 +0100
+++ lib/sasl/src/rb.erl	2009-09-23 20:39:09 +0200
@@ -415,7 +415,7 @@
 		    Ref = make_ref(),
 		    case (catch {Ref,binary_to_term(Bin)}) of
 			{'EXIT',_} ->
-			    {error, "Inclomplete erlang term in log"};
+			    {error, "Incomplete erlang term in log"};
 			{Ref,Term} ->
 			    {ok, Term}
 		    end
Index: lib/snmp/src/misc/snmp_config.erl
--- lib/snmp/src/misc/snmp_config.erl.orig	2009-09-18 16:12:14 +0200
+++ lib/snmp/src/misc/snmp_config.erl	2009-09-23 20:39:09 +0200
@@ -1743,7 +1743,7 @@
 "%% {\"standard inform\", \"std_inform\", inform}.\n"
 "%%\n\n",
     Hdr = header() ++ Comment, 
-    Conf = [{"stadard_trap", "std_trap", NotifyType}],
+    Conf = [{"standard trap", "std_trap", NotifyType}],
     write_agent_notify_config(Dir, Hdr, Conf).
 
 write_agent_notify_config(Dir, Hdr, Conf) ->
Index: lib/stdlib/src/calendar.erl
--- lib/stdlib/src/calendar.erl.orig	2009-09-18 16:06:56 +0200
+++ lib/stdlib/src/calendar.erl	2009-09-23 20:39:09 +0200
@@ -216,11 +216,19 @@
 
 -spec local_time_to_universal_time_dst(t_datetime1970()) -> [t_datetime1970()].
 local_time_to_universal_time_dst(DateTime) ->
-    UtDst = erlang:localtime_to_universaltime(DateTime, true),
-    Ut    = erlang:localtime_to_universaltime(DateTime, false),
     %% Reverse check the universal times
-    LtDst = erlang:universaltime_to_localtime(UtDst),
-    Lt    = erlang:universaltime_to_localtime(Ut),
+    {UtDst, LtDst} =
+        try
+            UtDst0 = erlang:localtime_to_universaltime(DateTime, true),
+            {UtDst0, erlang:universaltime_to_localtime(UtDst0)}
+        catch error:badarg -> {error, error}
+        end,
+    {Ut, Lt} =
+        try
+            Ut0 = erlang:localtime_to_universaltime(DateTime, false),
+            {Ut0, erlang:universaltime_to_localtime(Ut0)}
+        catch error:badarg -> {error, error}
+        end,
     %% Return the valid universal times
     case {LtDst,Lt} of
 	{DateTime,DateTime} when UtDst =/= Ut ->
Index: lib/wx/configure
--- lib/wx/configure.orig	2009-09-21 11:29:46 +0200
+++ lib/wx/configure	2009-09-23 20:39:09 +0200
@@ -3901,7 +3901,7 @@
 	;;
     *)
 	DEBUG_CFLAGS="-g -Wall -fPIC -DDEBUG $CFLAGS"
-	CFLAGS="-g -Wall -O2 -fPIC -fomit-frame-pointer -fno-strict-aliasing $CFLAGS"
+	CFLAGS="-Wall -fPIC -fomit-frame-pointer -fno-strict-aliasing $CFLAGS %%CFLAGS%%"
 	;;
 esac
 
