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

Subversion Repositories openrisc

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

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do compile }
2
! { dg-options "-fcheck=bounds" }
3
!
4
! PR 42804: ICE with -fcheck=bounds and type bound procedure call on array element
5
!
6
! Contributed by Ian Harvey 
7
 
8
MODULE ModA
9
  IMPLICIT NONE
10
  TYPE, PUBLIC :: A
11
    PROCEDURE(a_proc),pointer :: Proc
12
  END TYPE A
13
CONTAINS
14
  SUBROUTINE a_proc(this, stat)
15
    CLASS(A), INTENT(INOUT) :: this
16
    INTEGER, INTENT(OUT) :: stat
17
    WRITE (*, *) 'a_proc'
18
    stat = 0
19
  END SUBROUTINE a_proc
20
END MODULE ModA
21
 
22
PROGRAM ProgA
23
  USE ModA
24
  IMPLICIT NONE
25
  INTEGER :: ierr
26
  INTEGER :: i
27
  TYPE(A), ALLOCATABLE :: arr(:)
28
  ALLOCATE(arr(2))
29
  DO i = 1, 2
30
    arr(i)%proc => a_proc
31
    CALL arr(i)%Proc(ierr)
32
  END DO
33
END PROGRAM ProgA
34
 
35
! { dg-final { cleanup-modules "moda" } }

powered by: WebSVN 2.1.0

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