diff --git a/boehm-gc/ChangeLog b/boehm-gc/ChangeLog
index 542ddc1e0b62e56f3bd75013501c7734b75798e9..0591dd6068a69ff20ce56e8184531fff1f41752b 100644
--- a/boehm-gc/ChangeLog
+++ b/boehm-gc/ChangeLog
@@ -1,3 +1,60 @@
+2010-03-21  Dave Korn  <dave.korn.cygwin@gmail.com>
+
+	PR target/42811 (prerequisite)
+	* include/private/gc_priv.h (struct roots) [CYGWIN32]: Don't
+	declare r_next member on Cygwin as on other windows hosts.
+	(LOG_RT_SIZE) [CYGWIN32]: Don't define likewise.
+	(RT_SIZE) [CYGWIN32]: Likewise.
+	(struct _GC_arrays) [CYGWIN32]: Do declare _heap_bases[] member
+	likewise.
+	(GC_heap_bases) [CYGWIN32]: Do define likewise.
+	(struct _SYSTEM_INFO) [CYGWIN32]: Do forward-declare likewise.
+	(GC_sysinfo) [CYGWIN32]: Do declare extern likewise.
+	(GC_n_heap_bases) [CYGWIN32]: Likewise.
+	(GC_is_tmp_root) [CYGWIN32]: Do prototype likewise.
+	* include/private/gcconfig.h (GC_win32_get_mem) [CYGWIN32]: Likewise.
+	(GET_MEM) [CYGWIN32]: Do define likewise.
+	* boehm-gc/ptr_chck.c (GC_is_visible) [CYGWIN32]: Do handle dynamic
+	registration likewise.
+	* boehm-gc/os_dep.c (GC_setpagesize) [CYGWIN32]: Do define likewise.
+	(GC_no_win32_dlls) [CYGWIN32]: Define as constant false, unlike
+	other windows hosts.
+	(GC_sysinfo) [CYGWIN32]: Define as on other windows hosts.
+	(GC_n_heap_bases) [CYGWIN32]: Likewise.
+	(GLOBAL_ALLOC_TEST) [CYGWIN32]: Likewise.
+	(GC_win32_get_mem) [CYGWIN32]: Likewise, but wrapping GC_unix_get_mem
+	rather than GlobalAlloc/VirtualAlloc.
+	(GC_win32_free_heap) [CYGWIN32]: Likewise, but wrapping free instead
+	of GlobalFree (even though the function body is optimised away).
+	* boehm-gc/mark_rts.c (add_roots_to_index) [CYGWIN32]: Define as on
+	other windows hosts.
+	(GC_add_roots_inner) [CYGWIN32]: Avoid overlapping or adjacent
+	intervals likewise.
+	(GC_clear_roots) [CYGWIN32]: Clear GC_root_index[] likewise.
+	(GC_rebuild_root_index) [CYGWIN32]: Define as on other windows hosts.
+	(GC_remove_tmp_roots) [CYGWIN32]: Call it likewise.
+	(GC_remove_roots) [CYGWIN32]: Don't define, as on other windows hosts.
+	(GC_is_tmp_root) [CYGWIN32]: Define, as on other windows hosts.
+	(GC_cond_register_dynamic_libraries) [CYGWIN32]: Handle temporary
+	roots and dynamic registration likewise.
+	* boehm-gc/dyn_load.c (GC_has_static_roots) [CYGWIN32]: Define as on
+	other windows hosts.
+	(GC_register_has_static_roots_callback) [CYGWIN32]: Likewise.
+	(GC_cond_add_roots) [CYGWIN32]: Likewise.
+	(GC_register_main_static_data) [CYGWIN32]: Define to always return
+	false, as on MSWINCE
+	(HAVE_REGISTER_MAIN_STATIC_DATA) [CYGWIN32]: Define as on other
+	windows hosts.
+	(GC_warn_fb) [CYGWIN32]: Likewise.
+	(GC_disallow_ignore_fb) [CYGWIN32]: Likewise.
+	(GC_ignore_fb_mb) [CYGWIN32]: Likewise.
+	(GC_ignore_fb) [CYGWIN32]: Likewise.
+	(is_frame_buffer) [CYGWIN32]: Likewise.
+	(GC_dump_meminfo) [CYGWIN32]: Likewise.
+	(GC_wnt) [CYGWIN32]: Define to constant true.
+	(GC_register_dynamic_libraries) [CYGWIN32]: Define as on other
+	windows hosts.
+
 2009-12-09  Matthias Klose  <doko@ubuntu.com> 
 
 	* include/private/gc_locks.h: For __ARM_EABI__ define
diff --git a/boehm-gc/dyn_load.c b/boehm-gc/dyn_load.c
index 200abde7810b4d74d82db42cab53693ff0fde49a..5bebc1c155d13e6f4670a6a3cbfed073b22aa331 100644
--- a/boehm-gc/dyn_load.c
+++ b/boehm-gc/dyn_load.c
@@ -49,10 +49,13 @@
 #   undef GC_must_restore_redefined_dlopen
 # endif
 
-#if (defined(DYNAMIC_LOADING) || defined(MSWIN32) || defined(MSWINCE)) \
+#if (defined(DYNAMIC_LOADING) \
+	|| defined(MSWIN32)   \
+	|| defined(MSWINCE)   \
+	|| defined(CYGWIN32)) \
     && !defined(PCR)
 #if !defined(SUNOS4) && !defined(SUNOS5DL) && !defined(IRIX5) && \
-    !defined(MSWIN32) && !defined(MSWINCE) && \
+    !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32) && \
     !(defined(ALPHA) && defined(OSF1)) && \
     !defined(HPUX) && !(defined(LINUX) && defined(__ELF__)) && \
     !defined(RS6000) && !defined(SCO_ELF) && !defined(DGUX) && \
@@ -717,7 +720,7 @@ void GC_register_dynamic_libraries()
 
 # endif /* USE_PROC || IRIX5 */
 
-# if defined(MSWIN32) || defined(MSWINCE)
+# if defined(MSWIN32) || defined(MSWINCE) || defined(CYGWIN32)
 
 # define WIN32_LEAN_AND_MEAN
 # define NOSERVICE
@@ -761,7 +764,7 @@ void GC_register_dynamic_libraries()
     }
 # endif
 
-# ifdef MSWINCE
+# if defined(MSWINCE) || defined(CYGWIN32)
   /* Do we need to separately register the main static data segment? */
   GC_bool GC_register_main_static_data()
   {
@@ -868,8 +871,12 @@ void GC_register_dynamic_libraries()
   }
 # endif /* DEBUG_VIRTUALQUERY */
 
-  extern GC_bool GC_wnt;  /* Is Windows NT derivative.		*/
-  			  /* Defined and set in os_dep.c.	*/
+# ifdef CYGWIN32
+#   define GC_wnt (TRUE)
+# else
+    extern GC_bool GC_wnt;  /* Is Windows NT derivative.	*/
+  			    /* Defined and set in os_dep.c.	*/
+# endif
 
   void GC_register_dynamic_libraries()
   {
@@ -934,7 +941,7 @@ void GC_register_dynamic_libraries()
     GC_cond_add_roots(base, limit);
   }
 
-#endif /* MSWIN32 || MSWINCE */
+#endif /* MSWIN32 || MSWINCE || CYGWIN32 */
   
 #if defined(ALPHA) && defined(OSF1)
 
diff --git a/boehm-gc/include/private/gc_priv.h b/boehm-gc/include/private/gc_priv.h
index fdebe3688a52ea5c7d48d8955ec71d3bcd32b14f..4dbfa7d1fedb18e992178fd6b7b11fd9a582902e 100644
--- a/boehm-gc/include/private/gc_priv.h
+++ b/boehm-gc/include/private/gc_priv.h
@@ -833,14 +833,14 @@ struct exclusion {
 struct roots {
 	ptr_t r_start;
 	ptr_t r_end;
-#	if !defined(MSWIN32) && !defined(MSWINCE)
+#	if !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32)
 	  struct roots * r_next;
 #	endif
 	GC_bool r_tmp;
 	  	/* Delete before registering new dynamic libraries */
 };
 
-#if !defined(MSWIN32) && !defined(MSWINCE)
+#if !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32)
     /* Size of hash table index to roots.	*/
 #   define LOG_RT_SIZE 6
 #   define RT_SIZE (1 << LOG_RT_SIZE) /* Power of 2, may be != MAX_ROOT_SETS */
@@ -1024,7 +1024,7 @@ struct _GC_arrays {
   struct HeapSect {
       ptr_t hs_start; word hs_bytes;
   } _heap_sects[MAX_HEAP_SECTS];
-# if defined(MSWIN32) || defined(MSWINCE)
+# if defined(MSWIN32) || defined(MSWINCE) || defined(CYGWIN32)
     ptr_t _heap_bases[MAX_HEAP_SECTS];
     		/* Start address of memory regions obtained from kernel. */
 # endif
@@ -1033,7 +1033,7 @@ struct _GC_arrays {
     		/* Commited lengths of memory regions obtained from kernel. */
 # endif
   struct roots _static_roots[MAX_ROOT_SETS];
-# if !defined(MSWIN32) && !defined(MSWINCE)
+# if !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32)
     struct roots * _root_index[RT_SIZE];
 # endif
   struct exclusion _excl_table[MAX_EXCLUSIONS];
@@ -1091,7 +1091,7 @@ GC_API GC_FAR struct _GC_arrays GC_arrays;
 # ifdef USE_MUNMAP
 #   define GC_unmapped_bytes GC_arrays._unmapped_bytes
 # endif
-# if defined(MSWIN32) || defined(MSWINCE)
+# if defined(MSWIN32) || defined(MSWINCE) || defined (CYGWIN32)
 #   define GC_heap_bases GC_arrays._heap_bases
 # endif
 # ifdef MSWINCE
@@ -1187,7 +1187,7 @@ extern word GC_n_heap_sects;	/* Number of separately added heap	*/
 
 extern word GC_page_size;
 
-# if defined(MSWIN32) || defined(MSWINCE)
+# if defined(MSWIN32) || defined(MSWINCE) || defined(CYGWIN32)
   struct _SYSTEM_INFO;
   extern struct _SYSTEM_INFO GC_sysinfo;
   extern word GC_n_heap_bases;	/* See GC_heap_bases.	*/
@@ -1479,7 +1479,7 @@ void GC_remove_roots_inner GC_PROTO((char * b, char * e));
 GC_bool GC_is_static_root GC_PROTO((ptr_t p));
   		/* Is the address p in one of the registered static	*/
   		/* root sections?					*/
-# if defined(MSWIN32) || defined(_WIN32_WCE_EMULATION)
+# if defined(MSWIN32) || defined(_WIN32_WCE_EMULATION) || defined(CYGWIN32)
 GC_bool GC_is_tmp_root GC_PROTO((ptr_t p));
 		/* Is the address p in one of the temporary static	*/
 		/* root sections?					*/
diff --git a/boehm-gc/include/private/gcconfig.h b/boehm-gc/include/private/gcconfig.h
index 56e483c8d9519ec053089c4e9a8bac31adc3b118..c729130cb26b8cd54fd1a5c96581155f98274782 100644
--- a/boehm-gc/include/private/gcconfig.h
+++ b/boehm-gc/include/private/gcconfig.h
@@ -2375,7 +2375,7 @@
 					      calloc(1, (size_t)bytes + GC_page_size) \
 					      + GC_page_size-1)
 #     else
-#	ifdef MSWIN32
+#	if defined(MSWIN32) || defined(CYGWIN32)
 	  extern ptr_t GC_win32_get_mem();
 #         define GET_MEM(bytes) (struct hblk *)GC_win32_get_mem(bytes)
 #	else
diff --git a/boehm-gc/mark_rts.c b/boehm-gc/mark_rts.c
index 7a9fb8f2b7215f4d215b7413fc0795d0767c9d9a..94eb0ddb37f3e81f70260e9361e67f517cce81f7 100644
--- a/boehm-gc/mark_rts.c
+++ b/boehm-gc/mark_rts.c
@@ -22,7 +22,7 @@
 struct roots {
 	ptr_t r_start;
 	ptr_t r_end;
- #	if !defined(MSWIN32) && !defined(MSWINCE)
+ #	if !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32)
 	  struct roots * r_next;
  #	endif
 	GC_bool r_tmp;
@@ -87,7 +87,7 @@ ptr_t p;
     return(FALSE);
 }
 
-#if !defined(MSWIN32) && !defined(MSWINCE)
+#if !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32)
 /* 
 #   define LOG_RT_SIZE 6
 #   define RT_SIZE (1 << LOG_RT_SIZE)  -- Power of 2, may be != MAX_ROOT_SETS
@@ -139,7 +139,7 @@ struct roots *p;
     GC_root_index[h] = p;
 }
 
-# else /* MSWIN32 || MSWINCE */
+# else /* MSWIN32 || MSWINCE || CYGWIN32 */
 
 #   define add_roots_to_index(p)
 
@@ -175,7 +175,7 @@ GC_bool tmp;
 {
     struct roots * old;
     
-#   if defined(MSWIN32) || defined(MSWINCE)
+#   if defined(MSWIN32) || defined(MSWINCE) || defined(CYGWIN32)
       /* Spend the time to ensure that there are no overlapping	*/
       /* or adjacent intervals.					*/
       /* This could be done faster with e.g. a			*/
@@ -244,7 +244,7 @@ GC_bool tmp;
     GC_static_roots[n_root_sets].r_start = (ptr_t)b;
     GC_static_roots[n_root_sets].r_end = (ptr_t)e;
     GC_static_roots[n_root_sets].r_tmp = tmp;
-#   if !defined(MSWIN32) && !defined(MSWINCE)
+#   if !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32)
       GC_static_roots[n_root_sets].r_next = 0;
 #   endif
     add_roots_to_index(GC_static_roots + n_root_sets);
@@ -263,7 +263,7 @@ void GC_clear_roots GC_PROTO((void))
     roots_were_cleared = TRUE;
     n_root_sets = 0;
     GC_root_size = 0;
-#   if !defined(MSWIN32) && !defined(MSWINCE)
+#   if !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32)
     {
     	register int i;
     	
@@ -285,7 +285,7 @@ int i;
     n_root_sets--;
 }
 
-#if !defined(MSWIN32) && !defined(MSWINCE)
+#if !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32)
 static void GC_rebuild_root_index()
 {
     register int i;
@@ -308,12 +308,12 @@ void GC_remove_tmp_roots()
     	    i++;
     }
     }
-    #if !defined(MSWIN32) && !defined(MSWINCE)
+    #if !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32)
     GC_rebuild_root_index();
     #endif
 }
 
-#if !defined(MSWIN32) && !defined(MSWINCE)
+#if !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32)
 void GC_remove_roots(b, e)
 char * b; char * e;
 {
@@ -340,9 +340,9 @@ char * b; char * e;
     }
     GC_rebuild_root_index();
 }
-#endif /* !defined(MSWIN32) && !defined(MSWINCE) */
+#endif /* !defined(MSWIN32) && !defined(MSWINCE) && !defined(CYGWIN32) */
 
-#if defined(MSWIN32) || defined(_WIN32_WCE_EMULATION)
+#if defined(MSWIN32) || defined(_WIN32_WCE_EMULATION) || defined(CYGWIN32)
 /* Workaround for the OS mapping and unmapping behind our back:		*/
 /* Is the address p in one of the temporary static root sections?	*/
 GC_bool GC_is_tmp_root(p)
@@ -364,7 +364,7 @@ ptr_t p;
     }
     return(FALSE);
 }
-#endif /* MSWIN32 || _WIN32_WCE_EMULATION */
+#endif /* MSWIN32 || _WIN32_WCE_EMULATION || defined(CYGWIN32) */
 
 ptr_t GC_approx_sp()
 {
@@ -557,7 +557,7 @@ void GC_push_gc_structures GC_PROTO((void))
 void GC_cond_register_dynamic_libraries()
 {
 # if (defined(DYNAMIC_LOADING) || defined(MSWIN32) || defined(MSWINCE) \
-     || defined(PCR)) && !defined(SRC_M3)
+     || defined(CYGWIN32) || defined(PCR)) && !defined(SRC_M3)
     GC_remove_tmp_roots();
     if (!GC_no_dls) GC_register_dynamic_libraries();
 # else
diff --git a/boehm-gc/os_dep.c b/boehm-gc/os_dep.c
index 6f1e81abc16dae1147ee5e10c03521ee71010b49..ca8be1a8236cbd149a75aed7fb21c7de8b994d62 100644
--- a/boehm-gc/os_dep.c
+++ b/boehm-gc/os_dep.c
@@ -107,7 +107,7 @@
 # undef GC_AMIGA_DEF
 #endif
 
-#if defined(MSWIN32) || defined(MSWINCE)
+#if defined(MSWIN32) || defined(MSWINCE) || defined(CYGWIN32)
 # define WIN32_LEAN_AND_MEAN
 # define NOSERVICE
 # include <windows.h>
@@ -584,7 +584,7 @@ void GC_enable_signals()
 /* Find the page size */
 word GC_page_size;
 
-# if defined(MSWIN32) || defined(MSWINCE)
+# if defined(MSWIN32) || defined(MSWINCE) || defined (CYGWIN32)
   void GC_setpagesize()
   {
     GetSystemInfo(&GC_sysinfo);
@@ -1169,7 +1169,11 @@ void GC_register_data_segments()
 
 # else /* !OS2 */
 
-# if defined(MSWIN32) || defined(MSWINCE)
+# if defined(MSWIN32) || defined(MSWINCE) || defined (CYGWIN32)
+
+# ifdef CYGWIN32
+#    define GC_no_win32_dlls (FALSE)
+# endif
 
 # ifdef MSWIN32
   /* Unfortunately, we have to handle win32s very differently from NT, 	*/
@@ -1664,11 +1668,13 @@ void * os2_alloc(size_t bytes)
 # endif /* OS2 */
 
 
-# if defined(MSWIN32) || defined(MSWINCE)
+# if defined(MSWIN32) || defined(MSWINCE) || defined(CYGWIN32)
 SYSTEM_INFO GC_sysinfo;
 # endif
 
-# ifdef MSWIN32
+# if defined(MSWIN32) || defined(CYGWIN32)
+
+word GC_n_heap_bases = 0;
 
 # ifdef USE_GLOBAL_ALLOC
 #   define GLOBAL_ALLOC_TEST 1
@@ -1676,13 +1682,14 @@ SYSTEM_INFO GC_sysinfo;
 #   define GLOBAL_ALLOC_TEST GC_no_win32_dlls
 # endif
 
-word GC_n_heap_bases = 0;
-
 ptr_t GC_win32_get_mem(bytes)
 word bytes;
 {
     ptr_t result;
 
+# ifdef CYGWIN32
+    result = GC_unix_get_mem (bytes);
+# else
     if (GLOBAL_ALLOC_TEST) {
     	/* VirtualAlloc doesn't like PAGE_EXECUTE_READWRITE.	*/
     	/* There are also unconfirmed rumors of other		*/
@@ -1702,6 +1709,7 @@ word bytes;
     				      MEM_COMMIT | MEM_RESERVE,
     				      PAGE_EXECUTE_READWRITE);
     }
+#endif
     if (HBLKDISPL(result) != 0) ABORT("Bad VirtualAlloc result");
     	/* If I read the documentation correctly, this can	*/
     	/* only happen if HBLKSIZE > 64k or not a power of 2.	*/
@@ -1714,7 +1722,11 @@ void GC_win32_free_heap ()
 {
     if (GC_no_win32_dlls) {
  	while (GC_n_heap_bases > 0) {
+# ifdef CYGWIN32
+ 	    free (GC_heap_bases[--GC_n_heap_bases]);
+# else
  	    GlobalFree (GC_heap_bases[--GC_n_heap_bases]);
+# endif
  	    GC_heap_bases[GC_n_heap_bases] = 0;
  	}
     }
diff --git a/boehm-gc/ptr_chck.c b/boehm-gc/ptr_chck.c
index d83d730d3433f5f29b2da36e1c97013869b92394..09c86cb599d183d8f5e344e388ef9de1817dea57 100644
--- a/boehm-gc/ptr_chck.c
+++ b/boehm-gc/ptr_chck.c
@@ -247,7 +247,7 @@ ptr_t p;
     	    if (GC_is_static_root(p)) return(p);
     	    /* Else do it again correctly:	*/
 #           if (defined(DYNAMIC_LOADING) || defined(MSWIN32) || \
-		defined(MSWINCE) || defined(PCR)) \
+		defined(MSWINCE) || defined (CYGWIN32) || defined(PCR)) \
                 && !defined(SRC_M3)
     	        DISABLE_SIGNALS();
     	        GC_register_dynamic_libraries();