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

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [coarray_lock_4.f90] - Blame information for rev 801

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

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do compile }
2
! { dg-options "-fcoarray=single" }
3
!
4
!
5
! LOCK/LOCK_TYPE checks
6
!
7
 
8
subroutine valid()
9
  use iso_fortran_env
10
  implicit none
11
  type t
12
    type(lock_type) :: lock
13
  end type t
14
 
15
  type t2
16
    type(lock_type), allocatable :: lock(:)[:]
17
  end type t2
18
 
19
  type(t), save :: a[*]
20
  type(t2), save :: b ! OK
21
 
22
  allocate(b%lock(1)[*])
23
  LOCK(a%lock) ! OK
24
  LOCK(a[1]%lock) ! OK
25
 
26
  LOCK(b%lock(1)) ! OK
27
  LOCK(b%lock(1)[1]) ! OK
28
end subroutine valid
29
 
30
subroutine invalid()
31
  use iso_fortran_env
32
  implicit none
33
  type t
34
    type(lock_type) :: lock
35
  end type t
36
  type(t), save :: a ! { dg-error "type LOCK_TYPE or with subcomponent of type LOCK_TYPE must be a coarray" }
37
end subroutine invalid
38
 
39
subroutine more_tests
40
  use iso_fortran_env
41
  implicit none
42
  type t
43
    type(lock_type) :: a ! OK
44
  end type t
45
 
46
  type t1
47
    type(lock_type), allocatable :: c2(:)[:] ! OK
48
  end type t1
49
  type(t1) :: x1 ! OK
50
 
51
  type t2
52
    type(lock_type), allocatable :: c1(:) ! { dg-error "Allocatable component c1 at .1. of type LOCK_TYPE must have a codimension" }
53
  end type t2
54
 
55
  type t3
56
    type(t) :: b
57
  end type t3
58
  type(t3) :: x3 ! { dg-error "of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must be a coarray" }
59
 
60
  type t4
61
    type(lock_type) :: c0(2)
62
  end type t4
63
  type(t4) :: x4 ! { dg-error "of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must be a coarray" }
64
end subroutine more_tests

powered by: WebSVN 2.1.0

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