diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index e9c37c9c88cea51e3352dec2fc0ecb726855c03e..c1ab201a9efa256278daec4e76a094ffe230207a 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2016-11-30  Andre Vehreschild  <vehre@gcc.gnu.org>
+
+	Now really add the file.
+	* gfortran.dg/coarray_lib_alloc_4.f90: New test.
+
 2016-11-30  David Edelsohn  <dje.gcc@gmail.com>
 
 	* g++.dg/eh/new1.C: XFAIL on AIX.
@@ -33,11 +38,6 @@
 	PR tree-optimization/78574
 	* gcc.c-torture/compile/pr78574.c: New test.
 
-2016-11-30  Andre Vehreschild  <vehre@gcc.gnu.org>
-
-	* caf/single.c (_gfortran_caf_is_present): Prevent fallthrough
-	warnings.
-
 2016-11-30  Andre Vehreschild  <vehre@gcc.gnu.org>
 
 	* gfortran.dg/coarray/alloc_comp_1.f90: Fix tree-dump scans to adhere
diff --git a/gcc/testsuite/gfortran.dg/coarray_lib_alloc_4.f90 b/gcc/testsuite/gfortran.dg/coarray_lib_alloc_4.f90
new file mode 100644
index 0000000000000000000000000000000000000000..aea9fbf7f98d62d47d5e9770241f668aa318360c
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/coarray_lib_alloc_4.f90
@@ -0,0 +1,46 @@
+! { dg-do run }
+! { dg-options "-fcoarray=lib -lcaf_single -fdump-tree-original" }
+!
+! Allocate/deallocate with libcaf.
+!
+
+program test_caf_alloc
+
+  type t
+    integer, allocatable :: i
+    real, allocatable :: r(:)
+  end type t
+
+  type(t), allocatable :: xx[:]
+
+  allocate (xx[*])
+
+  if (allocated(xx%i)) call abort()
+  if (allocated(xx[1]%i)) call abort()
+  if (allocated(xx[1]%r)) call abort()
+  allocate(xx%i)
+  if (.not. allocated(xx[1]%i)) call abort()
+  if (allocated(xx[1]%r)) call abort()
+  
+  allocate(xx%r(5))
+  if (.not. allocated(xx[1]%i)) call abort()
+  if (.not. allocated(xx[1]%r)) call abort()
+  
+  deallocate(xx%i)
+  if (allocated(xx[1]%i)) call abort()
+  if (.not. allocated(xx[1]%r)) call abort()
+
+  deallocate(xx%r)
+  if (allocated(xx[1]%i)) call abort()
+  if (allocated(xx[1]%r)) call abort()
+
+  deallocate(xx)
+end
+
+! { dg-final { scan-tree-dump-times "_gfortran_caf_is_present \\(xx\\.token, 2 - \\(integer\\(kind=4\\)\\) xx\\.dim\\\[0\\\]\\.lbound, &caf_ref\\.\[0-9\]+\\)|_gfortran_caf_is_present \\(xx\\.token, 2 - xx\\.dim\\\[0\\\]\\.lbound, &caf_ref\\.\[0-9\]+\\)" 10 "original" } }
+! { dg-final { scan-tree-dump-times "_gfortran_caf_register \\(72, 1, &xx\\.token, \\(void \\*\\) &xx, 0B, 0B, 0\\)" 1 "original" } }
+! { dg-final { scan-tree-dump-times "_gfortran_caf_register \\(\[0-9\]+, 7" 2 "original" } }
+! { dg-final { scan-tree-dump-times "_gfortran_caf_register \\(\[0-9\]+, 8" 2 "original" } }
+! { dg-final { scan-tree-dump-times "_gfortran_caf_deregister \\(&xx\\.token, 0, 0B, 0B, 0\\)" 1 "original" } }
+! { dg-final { scan-tree-dump-times "_gfortran_caf_deregister \\(&\\(\\(struct t \\* restrict\\) xx\\.data\\)->r\\.token, 1, 0B, 0B, 0\\)" 1 "original" } }
+! { dg-final { scan-tree-dump-times "_gfortran_caf_deregister \\(&\\(\\(struct t \\* restrict\\) xx\\.data\\)->_caf_i, 1, 0B, 0B, 0\\)" 1 "original" } }
diff --git a/libgfortran/ChangeLog b/libgfortran/ChangeLog
index 97dda7b92d979f1ac461b70d89fa1bd9da43f589..d3966f5d54cdae6cd4d08b0dfaa655516ce8282a 100644
--- a/libgfortran/ChangeLog
+++ b/libgfortran/ChangeLog
@@ -1,3 +1,10 @@
+2016-11-30  Andre Vehreschild  <vehre@gcc.gnu.org>
+
+	* caf/single.c (_gfortran_caf_get_by_ref): Prevent compile time
+	warning.
+	(_gfortran_caf_send_by_ref): Same.
+	(_gfortran_caf_is_present): Prevent fallthrough	warnings.
+
 2016-11-30  Andre Vehreschild  <vehre@gcc.gnu.org>
 
 	* caf/libcaf.h: Add new action types for (de-)registration of
diff --git a/libgfortran/caf/single.c b/libgfortran/caf/single.c
index 3eceed90087593d4bf000ca12b480cf16e74a3a5..d1b33592502c344b3773c6bb561e51299faebd01 100644
--- a/libgfortran/caf/single.c
+++ b/libgfortran/caf/single.c
@@ -1471,7 +1471,7 @@ _gfortran_caf_get_by_ref (caf_token_t token,
   size_t dst_index[GFC_MAX_DIMENSIONS];
   int dst_rank = GFC_DESCRIPTOR_RANK (dst);
   int dst_cur_dim = 0;
-  size_t src_size;
+  size_t src_size = 0;
   caf_single_token_t single_token = TOKEN (token);
   void *memptr = single_token->memptr;
   gfc_descriptor_t *src = single_token->desc;
@@ -2325,7 +2325,7 @@ _gfortran_caf_send_by_ref (caf_token_t token,
   size_t dst_index[GFC_MAX_DIMENSIONS];
   int src_rank = GFC_DESCRIPTOR_RANK (src);
   int src_cur_dim = 0;
-  size_t src_size;
+  size_t src_size = 0;
   caf_single_token_t single_token = TOKEN (token);
   void *memptr = single_token->memptr;
   gfc_descriptor_t *dst = single_token->desc;