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

Subversion Repositories openrisc

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc2/] [gcc/] [testsuite/] [gfortran.dg/] [interface_25.f90] - Blame information for rev 384

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 302 jeremybenn
! { dg-do compile }
2
! Tests the fix for PR39295, in which the check of the interfaces
3
! at lines 25 and 42 failed because opfunc1 is identified as a
4
! function by usage, whereas opfunc2 is not.
5
!
6
! Contributed by Jon Hurst 
7
!
8
MODULE  funcs
9
CONTAINS
10
  INTEGER FUNCTION test1(a,b,opfunc1)
11
    INTEGER :: a,b
12
    INTEGER, EXTERNAL :: opfunc1
13
    test1 = opfunc1( a, b )
14
  END FUNCTION test1
15
  INTEGER FUNCTION sumInts(a,b)
16
    INTEGER :: a,b
17
    sumInts = a + b
18
  END FUNCTION sumInts
19
END MODULE funcs
20
 
21
PROGRAM test
22
  USE funcs
23
  INTEGER :: rs
24
  INTEGER, PARAMETER :: a = 2, b = 1
25
  rs = recSum( a, b, test1, sumInts )
26
  write(*,*) "Results", rs
27
CONTAINS
28
  RECURSIVE INTEGER FUNCTION recSum( a,b,UserFunction,UserOp ) RESULT( res )
29
    IMPLICIT NONE
30
    INTEGER :: a,b
31
    INTERFACE
32
       INTEGER FUNCTION UserFunction(a,b,opfunc2)
33
         INTEGER :: a,b
34
         INTEGER, EXTERNAL :: opfunc2
35
       END FUNCTION UserFunction
36
    END INTERFACE
37
    INTEGER, EXTERNAL :: UserOp
38
 
39
    res = UserFunction( a,b, UserOp )
40
 
41
    if( res .lt. 10 ) then
42
       res = recSum( a, res, UserFunction, UserOp )
43
    end if
44
  END FUNCTION recSum
45
END PROGRAM test

powered by: WebSVN 2.1.0

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