OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [warn_implicit_procedure_1.f90] - Blame information for rev 302

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 302 jeremybenn
! { dg-do compile }
2
! { dg-options "-Wimplicit-procedure" }
3
 
4
! PR fortran/22552
5
! Check for correct -Wimplicit-procedure warnings.
6
 
7
MODULE m
8
 
9
CONTAINS
10
 
11
  SUBROUTINE my_sub ()
12
  END SUBROUTINE my_sub
13
 
14
  INTEGER FUNCTION my_func ()
15
    my_func = 42
16
  END FUNCTION my_func
17
 
18
END MODULE m
19
 
20
SUBROUTINE test (proc)
21
  IMPLICIT NONE
22
  CALL proc () ! { dg-bogus "is not explicitly declared" }
23
END SUBROUTINE test
24
 
25
PROGRAM main
26
  USE m
27
  EXTERNAL :: ext_sub
28
  EXTERNAL :: test
29
  INTEGER :: ext_func
30
 
31
  CALL ext_sub () ! { dg-bogus "is not explicitly declared" }
32
  PRINT *, ext_func () ! { dg-bogus "is not explicitly declared" }
33
  PRINT *, implicit_func () ! { dg-bogus "is not explicitly declared" }
34
  CALL my_sub () ! { dg-bogus "is not explicitly declared" }
35
  PRINT *, my_func () ! { dg-bogus "is not explicitly declared" }
36
  PRINT *, SIN (3.14159) ! { dg-bogus "is not explicitly declared" }
37
 
38
  CALL undef_sub (1, 2, 3) ! { dg-warning "is not explicitly declared" }
39
  ! Can't check undefined function, because it needs to be declared a type
40
  ! in any case (and the implicit type is enough to not trigger this warning).
41
END PROGRAM
42
 
43
! { dg-final { cleanup-modules "m" } }

powered by: WebSVN 2.1.0

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