diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index d511f9a1068ec19405c5a49651e4140065f0f513..7a536a72c1870925408cd3a1a23b6b049258b4a7 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2005-10-20  Erik Edelmann  <erik.edelmann@iki.fi>
+
+	PR fortran/21625
+	* gfortran.fg/der_init_1.f90: New.
+
 2005-10-19  Ulrich Weigand  <uweigand@de.ibm.com>
 
 	* gcc.dg/20050824-1.c (f): Clobber %r13 and %r14 only on s390x.
diff --git a/gcc/testsuite/gfortran.dg/derived_init_1.f90 b/gcc/testsuite/gfortran.dg/derived_init_1.f90
new file mode 100644
index 0000000000000000000000000000000000000000..bdd7d3773d7bbbbe5820f45c3655aeb8b287295b
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/derived_init_1.f90
@@ -0,0 +1,32 @@
+! { dg-do run }
+! Check that allocatable/pointer variables of derived types with initialized
+! components are are initialized when allocated
+! PR 21625
+program test
+
+    implicit none
+    type :: t
+        integer :: a = 3
+    end type t
+    type :: s
+        type(t), pointer :: p(:)
+        type(t), pointer :: p2
+    end type s
+    type(t), pointer :: p
+    type(t), allocatable :: q(:,:)
+    type(s) :: z
+    type(s) :: x(2)
+
+    allocate(p, q(2,2))
+    if (p%a /= 3) call abort()
+    if (any(q(:,:)%a /= 3)) call abort()
+
+    allocate(z%p2, z%p(2:3))
+    if (z%p2%a /= 3) call abort()
+    if (any(z%p(:)%a /= 3)) call abort()
+
+    allocate(x(1)%p2, x(1)%p(2))
+    if (x(1)%p2%a /= 3) call abort()
+    if (any(x(1)%p(:)%a /= 3)) call abort()
+end program test
+