OSDN Git Service

* gcc.dg/20020919-1.c: Correct target selector to alpha*-*-*.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / allocatable_dummy_1.f90
index db65d71..9aba8b8 100644 (file)
@@ -13,6 +13,8 @@ program alloc_dummy
     call useit(a, b)
     if (.NOT.all(b == [ 1, 2, 3 ])) call abort()
 
+    if (.NOT.all(whatever(a) == [ 1, 2, 3 ])) call abort()
+
     call kill(a)
     if (allocated(a)) call abort()
 
@@ -31,10 +33,17 @@ contains
         integer, allocatable, intent(in)  :: x(:)
         integer, allocatable, intent(out) :: y(:)
         if (allocated(y)) call abort()
-        allocate (y(3))
+        call init(y)
         y = x
     end subroutine useit
 
+    function whatever(x)
+        integer, allocatable :: x(:)
+        integer :: whatever(size(x))
+        
+        whatever = x
+    end function whatever
+
     subroutine kill(x)
         integer, allocatable, intent(out) :: x(:)
     end subroutine kill