aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/class_array_6.f03
blob: ab4766f9d0d2506566a0004b9464e5f6f981b57c (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
! { dg-do compile }
! PR46356 - class arrays 
!
! Contributed by Ian Harvey
!
MODULE procedure_intent_nonsense
  IMPLICIT NONE  
  PRIVATE    
  TYPE, PUBLIC :: Parent
    INTEGER :: comp
  END TYPE Parent

  TYPE :: ParentVector
    INTEGER :: a
    ! CLASS(Parent), ALLOCATABLE :: a
  END TYPE ParentVector  
CONTAINS           
  SUBROUTINE vector_operation(pvec)     
    CLASS(ParentVector), INTENT(INOUT) :: pvec(:)
    INTEGER :: i    
    !---
    DO i = 1, SIZE(pvec)
      CALL item_operation(pvec(i))
    END DO  
    ! PRINT *, pvec(1)%a%comp
  END SUBROUTINE vector_operation

  SUBROUTINE item_operation(pvec)  
    CLASS(ParentVector), INTENT(INOUT) :: pvec
    !TYPE(ParentVector), INTENT(INOUT) :: pvec
  END SUBROUTINE item_operation
END MODULE procedure_intent_nonsense