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

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [lto/] [pr45586_0.f90] - Blame information for rev 749

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-lto-do link }
2
      MODULE M1
3
      INTEGER, PARAMETER :: dp=8
4
      TYPE realspace_grid_type
5
 
6
          REAL(KIND=dp), DIMENSION ( :, :, : ), ALLOCATABLE :: r
7
 
8
      END TYPE realspace_grid_type
9
      END MODULE
10
 
11
      MODULE M2
12
      USE m1
13
      CONTAINS
14
      SUBROUTINE S1(x)
15
      TYPE(realspace_grid_type), POINTER :: x
16
      REAL(dp), DIMENSION(:, :, :), POINTER    :: y
17
      y=>x%r
18
      y=0
19
 
20
      END SUBROUTINE
21
      END MODULE
22
 
23
      USE M2
24
      TYPE(realspace_grid_type), POINTER :: x
25
      ALLOCATE(x)
26
      ALLOCATE(x%r(10,10,10))
27
      CALL S1(x)
28
      write(6,*) x%r
29
      END
30
 
31
! { dg-final { cleanup-modules "m1 m2" } }

powered by: WebSVN 2.1.0

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