diff gcc/testsuite/gfortran.dg/coarray_allocate_9.f08 @ 111:04ced10e8804

gcc 7
author kono
date Fri, 27 Oct 2017 22:46:09 +0900
parents
children 84e7813d76e9
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/gcc/testsuite/gfortran.dg/coarray_allocate_9.f08	Fri Oct 27 22:46:09 2017 +0900
@@ -0,0 +1,32 @@
+! { dg-do run }
+! { dg-options "-fcoarray=lib -lcaf_single" }
+! { dg-additional-options "-latomic" { target libatomic_available } }
+
+! Contributed by Damian Rouson
+
+program main
+  implicit none
+
+  type particles
+    real x(2)
+  end type
+
+  type vector
+    type(particles), allocatable :: v(:)
+  end type
+
+  type(vector) :: outbox[*]
+  type(particles), allocatable :: object(:)[:]
+
+  allocate(outbox%v(1), source=particles(this_image()))
+
+  if (any( outbox[1]%v(1)%x(1:2) /= [ 1.0, 1.0] )) call abort()
+  if (any( outbox[1]%v(1)%x(:) /= [ 1.0, 1.0] )) call abort()
+  if (any( outbox[1]%v(1)%x /= [ 1.0, 1.0] )) call abort()
+
+  allocate(object(1)[*], source=particles(this_image()))
+
+  if (any( object(1)[1]%x(1:2) /= [ 1.0, 1.0] )) call abort()
+  if (any( object(1)[1]%x(:) /= [ 1.0, 1.0] )) call abort()
+  if (any( object(1)[1]%x /= [ 1.0, 1.0] )) call abort()
+end program