diff gcc/testsuite/gfortran.dg/assumed_rank_2.f90 @ 132:d34655255c78

update gcc-8.2
author mir3636
date Thu, 25 Oct 2018 10:21:07 +0900
parents 84e7813d76e9
children
line wrap: on
line diff
--- a/gcc/testsuite/gfortran.dg/assumed_rank_2.f90	Thu Oct 25 08:08:40 2018 +0900
+++ b/gcc/testsuite/gfortran.dg/assumed_rank_2.f90	Thu Oct 25 10:21:07 2018 +0900
@@ -16,7 +16,7 @@
 
 allocate(z(1:4, -2:5, 4, 10:11))
 
-if (rank(x) /= 2) call abort ()
+if (rank(x) /= 2) STOP 1
 val = [(2*i+3, i = 1, size(x))]
 x = reshape (val, shape(x))
 call foo(x, rank(x), lbound(x), ubound(x), val)
@@ -24,7 +24,7 @@
 call bar(x,x,.true.)
 call bar(x,prsnt=.false.)
 
-if (rank(y) /= 1) call abort ()
+if (rank(y) /= 1) STOP 2
 val = [(2*i+7, i = 1, size(y))]
 y = reshape (val, shape(y))
 call foo(y, rank(y), lbound(y), ubound(y), val)
@@ -32,7 +32,7 @@
 call bar(y,y,.true.)
 call bar(y,prsnt=.false.)
 
-if (rank(z) /= 4) call abort ()
+if (rank(z) /= 4) STOP 3
 val = [(2*i+5, i = 1, size(z))]
 z(:,:,:,:) = reshape (val, shape(z))
 call foo(z, rank(z), lbound(z), ubound(z), val)
@@ -45,16 +45,16 @@
   subroutine bar(a,b, prsnt)
     integer, pointer, optional, intent(in) :: a(..),b(..)
     logical, value :: prsnt
-    if (.not. associated(a)) call abort()
+    if (.not. associated(a)) STOP 4
     if (present(b)) then
       ! The following is not valid
       ! Technically, it could be allowed and might be in Fortran 2015:
-      ! if (.not. associated(a,b)) call abort()
+      ! if (.not. associated(a,b)) STOP 5
     else
-      if (.not. associated(a)) call abort()
+      if (.not. associated(a)) STOP 6
     end if
-    if (.not. present(a)) call abort()
-    if (prsnt .neqv. present(b)) call abort()
+    if (.not. present(a)) STOP 7
+    if (prsnt .neqv. present(b)) STOP 8
   end subroutine
 
   ! POINTER argument - bounds as specified before
@@ -66,20 +66,20 @@
 
 
 
-    if (rank(a) /= rnk) call abort()
-    if (size(low) /= rnk .or. size(high) /= rnk) call abort()
-    if (size(a) /= product (high - low +1)) call abort()
+    if (rank(a) /= rnk) STOP 9
+    if (size(low) /= rnk .or. size(high) /= rnk) STOP 10
+    if (size(a) /= product (high - low +1)) STOP 11
 
     if (rnk > 0) then
-      if (low(1) /= lbound(a,1)) call abort()
-      if (high(1) /= ubound(a,1)) call abort()
-      if (size (a,1) /= high(1)-low(1)+1) call abort()
+      if (low(1) /= lbound(a,1)) STOP 12
+      if (high(1) /= ubound(a,1)) STOP 13
+      if (size (a,1) /= high(1)-low(1)+1) STOP 14
     end if
 
     do i = 1, rnk
-      if (low(i) /= lbound(a,i)) call abort()
-      if (high(i) /= ubound(a,i)) call abort()
-      if (size (a,i) /= high(i)-low(i)+1) call abort()
+      if (low(i) /= lbound(a,i)) STOP 15
+      if (high(i) /= ubound(a,i)) STOP 16
+      if (size (a,i) /= high(i)-low(i)+1) STOP 17
     end do
     call foo2(a, rnk, low, high, val)
   end subroutine
@@ -91,20 +91,20 @@
     integer, intent(in) :: low(:), high(:), val(:)
     integer :: i
 
-    if (rank(a) /= rnk) call abort()
-    if (size(low) /= rnk .or. size(high) /= rnk) call abort()
-    if (size(a) /= product (high - low +1)) call abort()
+    if (rank(a) /= rnk) STOP 18
+    if (size(low) /= rnk .or. size(high) /= rnk) STOP 19
+    if (size(a) /= product (high - low +1)) STOP 20
 
     if (rnk > 0) then
-      if (1 /= lbound(a,1)) call abort()
-      if (high(1)-low(1)+1 /= ubound(a,1)) call abort()
-      if (size (a,1) /= high(1)-low(1)+1) call abort()
+      if (1 /= lbound(a,1)) STOP 21
+      if (high(1)-low(1)+1 /= ubound(a,1)) STOP 22
+      if (size (a,1) /= high(1)-low(1)+1) STOP 23
     end if
 
     do i = 1, rnk
-      if (1 /= lbound(a,i)) call abort()
-      if (high(i)-low(i)+1 /= ubound(a,i)) call abort()
-      if (size (a,i) /= high(i)-low(i)+1) call abort()
+      if (1 /= lbound(a,i)) STOP 24
+      if (high(i)-low(i)+1 /= ubound(a,i)) STOP 25
+      if (size (a,i) /= high(i)-low(i)+1) STOP 26
     end do
   end subroutine foo2
 
@@ -115,20 +115,20 @@
     integer, intent(in) :: low(:), high(:), val(:)
     integer :: i
 
-    if (rank(a) /= rnk) call abort()
-    if (size(low) /= rnk .or. size(high) /= rnk) call abort()
-    if (size(a) /= product (high - low +1)) call abort()
+    if (rank(a) /= rnk) STOP 27
+    if (size(low) /= rnk .or. size(high) /= rnk) STOP 28
+    if (size(a) /= product (high - low +1)) STOP 29
 
     if (rnk > 0) then
-      if (low(1) /= lbound(a,1)) call abort()
-      if (high(1) /= ubound(a,1)) call abort()
-      if (size (a,1) /= high(1)-low(1)+1) call abort()
+      if (low(1) /= lbound(a,1)) STOP 30
+      if (high(1) /= ubound(a,1)) STOP 31
+      if (size (a,1) /= high(1)-low(1)+1) STOP 32
     end if
 
     do i = 1, rnk
-      if (low(i) /= lbound(a,i)) call abort()
-      if (high(i) /= ubound(a,i)) call abort()
-      if (size (a,i) /= high(i)-low(i)+1) call abort()
+      if (low(i) /= lbound(a,i)) STOP 33
+      if (high(i) /= ubound(a,i)) STOP 34
+      if (size (a,i) /= high(i)-low(i)+1) STOP 35
     end do
     call foo(a, rnk, low, high, val)
   end subroutine