aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/select_type_31.f03
blob: a2858121957be894507b96130c638a7568803bd5 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
! { dg-do compile }
! { dg-options "-fcoarray=single" }
! Test the fix for PR55172.
!
! Contributed by Arjen Markus  <arjen.markus@deltares.nl>
!
module gn
  type :: ncb
  end type ncb
  type, public :: tn
     class(ncb), allocatable, dimension(:) :: cb
  end type tn
contains
  integer function name(self)
    implicit none
    class (tn), intent(in) :: self
    select type (component => self%cb(i)) ! { dg-error "has no IMPLICIT type" }
    end select
  end function name
end module gn

! Further issues, raised by Tobias Burnus in the course of fixing the PR

module gn1
  type :: ncb1
  end type ncb1
  type, public :: tn1
     class(ncb1), allocatable, dimension(:) :: cb
  end type tn1
contains
  integer function name(self)
    implicit none
    class (tn1), intent(in) :: self
    select type (component => self%cb([4,7+1])) ! { dg-error "needs a temporary" }
    end select
  end function name
end module gn1

module gn2
  type :: ncb2
  end type ncb2
  type, public :: tn2
     class(ncb2), allocatable :: cb[:]
  end type tn2
contains
  integer function name(self)
    implicit none
    class (tn2), intent(in) :: self
    select type (component => self%cb[4]) ! { dg-error "must not be coindexed" }
    end select
  end function name
end module gn2