comparison gcc/testsuite/gfortran.dg/pr80668.f90 @ 111:04ced10e8804

gcc 7
author kono
date Fri, 27 Oct 2017 22:46:09 +0900
parents
children
comparison
equal deleted inserted replaced
68:561a7518be6b 111:04ced10e8804
1 ! { dg-do compile }
2 ! { dg-options "-finit-derived -finit-integer=12345678" }
3 !
4 ! PR fortran/80668
5 !
6 ! Test a regression where structure constructor expressions were created for
7 ! POINTER components with -finit-derived.
8 !
9
10 MODULE pr80668
11 IMPLICIT NONE
12 TYPE :: dist_t
13 INTEGER :: TYPE,nblks_loc,nblks
14 INTEGER,DIMENSION(:),POINTER :: dist
15 END TYPE dist_t
16
17 CONTAINS
18
19 SUBROUTINE hfx_new()
20 TYPE(dist_t) :: dist
21 integer,pointer :: bob
22 CALL release_dist(dist, bob)
23 END SUBROUTINE hfx_new
24
25 SUBROUTINE release_dist(dist,p)
26 TYPE(dist_t) :: dist
27 integer, pointer, intent(in) :: p
28 END SUBROUTINE release_dist
29 END MODULE