OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [coarray/] [dummy_1.f90] - Blame information for rev 749

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do run }
2
!
3
! PR fortran/18918
4
!
5
! Check whether assumed-shape's cobounds are properly handled
6
!
7
    implicit none
8
    integer :: B(1)[*]
9
    integer :: C(8:11)[-3:10,43:*]
10
    integer, allocatable :: D(:)[:,:]
11
 
12
    allocate (D(20)[2:3,5:*])
13
 
14
    call sub (B,5)
15
    call sub (C,3)
16
    call sub (D,3)
17
 
18
    call sub2 (B, -3)
19
    call sub2 (C, 44)
20
    call sub2 (D, 44)
21
 
22
    call sub3 (B)
23
    call sub3 (C)
24
    call sub3 (D)
25
 
26
    call sub4 (B)
27
    call sub4 (C)
28
    call sub4 (D)
29
 
30
    call sub5 (D)
31
  contains
32
 
33
  subroutine sub(A,n)
34
    integer :: n
35
    integer :: A(n:)[n:2*n,3*n:*]
36
    if (lbound(A,dim=1) /= n) call abort ()
37
    if (any (lcobound(A) /= [n, 3*n])) call abort ()
38
    if (ucobound(A, dim=1) /= 2*n) call abort()
39
  end subroutine sub
40
 
41
  subroutine sub2(A,n)
42
    integer :: n
43
    integer :: A(:)[-n:*]
44
    if (lbound(A,dim=1) /= 1) call abort ()
45
    if (lcobound(A, dim=1) /= -n) call abort ()
46
  end subroutine sub2
47
 
48
  subroutine sub3(A)
49
    integer :: A(:)[0,*]
50
    if (lbound(A,dim=1) /= 1) call abort ()
51
    if (lcobound(A, dim=1) /= 1) call abort ()
52
    if (ucobound(A, dim=1) /= 0) call abort ()
53
    if (lcobound(A, dim=2) /= 1) call abort ()
54
  end subroutine sub3
55
 
56
  subroutine sub4(A)
57
    integer :: A(:)[*]
58
    if (lbound(A,dim=1) /= 1) call abort ()
59
    if (lcobound(A, dim=1) /= 1) call abort ()
60
  end subroutine sub4
61
 
62
  subroutine sub5(A)
63
    integer, allocatable :: A(:)[:,:]
64
 
65
    if (lbound(A,dim=1) /= 1) call abort ()
66
    if (lcobound(A, dim=1) /= 2) call abort ()
67
    if (ucobound(A, dim=1) /= 3) call abort ()
68
    if (lcobound(A, dim=2) /= 5) call abort ()
69
  end subroutine sub5
70
  end

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.