Mercurial > hg > CbC > CbC_gcc
view gcc/testsuite/gfortran.dg/lto/pr45586-2_0.f90 @ 145:1830386684a0
gcc-9.2.0
author | anatofuz |
---|---|
date | Thu, 13 Feb 2020 11:34:05 +0900 |
parents | 04ced10e8804 |
children |
line wrap: on
line source
! { dg-lto-do link } ! ! PR fortran/45586 (comment 53) ! MODULE M1 INTEGER, PARAMETER :: dp=8 TYPE realspace_grid_type REAL(KIND=dp), DIMENSION ( :, :, : ), ALLOCATABLE :: r END TYPE realspace_grid_type TYPE realspace_grid_p_type TYPE(realspace_grid_type), POINTER :: rs_grid END TYPE realspace_grid_p_type TYPE realspaces_grid_p_type TYPE(realspace_grid_p_type), DIMENSION(:), POINTER :: rs END TYPE realspaces_grid_p_type END MODULE MODULE M2 USE M1 CONTAINS SUBROUTINE S1() INTEGER :: i,j TYPE(realspaces_grid_p_type), DIMENSION(:), POINTER :: rs_gauge REAL(dp), DIMENSION(:, :, :), POINTER :: y y=>rs_gauge(i)%rs(j)%rs_grid%r END SUBROUTINE END MODULE USE M2 CALL S1() END