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

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-old/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [implicit_10.f90] - Blame information for rev 853

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

Line No. Rev Author Line
1 149 jeremybenn
! { dg-do run }
2
! Check fix for PR24783 where we did try to resolve the implicit type
3
! from the wrong namespace thus rejecting valid code.
4
      MODULE mod1
5
      IMPLICIT NONE
6
      CONTAINS
7
      SUBROUTINE sub(vec, ny)
8
      IMPLICIT REAL (a-h,o-z)
9
      IMPLICIT INTEGER (i-n)
10
      DIMENSION vec(ny)
11
      ny = fun(vec(ny),1,1)
12
      RETURN
13
      END SUBROUTINE sub
14
      REAL FUNCTION fun(r1, i1, i2)
15
      IMPLICIT REAL (r,f)
16
      IMPLICIT INTEGER (i)
17
      DIMENSION r1(i1:i2)
18
      r1(i1) = i1 + 1
19
      r1(i2) = i2 + 1
20
      fun = r1(i1) + r1(i2)
21
      END FUNCTION fun
22
      END MODULE mod1
23
 
24
      use mod1
25
      IMPLICIT REAL (d)
26
      INTEGER i
27
      dimension di(5)
28
      i = 1
29
      if (fun(di(i),1,2).NE.5) call abort()
30
      call sub(di(i),i)
31
      if (i.NE.4) call abort()
32
      end
33
! { dg-final { cleanup-modules "mod1" } }

powered by: WebSVN 2.1.0

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