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

Subversion Repositories openrisc

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

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

Line No. Rev Author Line
1 149 jeremybenn
! { dg-do run }
2
! Tests the fix for PR26393, in which an ICE would occur in trans-decl.c
3
! (gfc_get_symbol_decl) because anzKomponenten is not referenced in the
4
! interface for solveCConvert. The solution was to assert that the symbol
5
! is either referenced or in an interface body.
6
!
7
! Based on the testcase in the PR.
8
!
9
  MODULE MODULE_CONC
10
    INTEGER, SAVE :: anzKomponenten = 2
11
  END MODULE MODULE_CONC
12
 
13
  MODULE MODULE_THERMOCALC
14
    INTERFACE
15
      FUNCTION solveCConvert ()
16
        USE MODULE_CONC, ONLY: anzKomponenten
17
        REAL :: solveCConvert(1:anzKomponenten)
18
        END FUNCTION solveCConvert
19
    END INTERFACE
20
  END MODULE MODULE_THERMOCALC
21
 
22
  SUBROUTINE outDiffKoeff
23
    USE MODULE_CONC
24
    USE MODULE_THERMOCALC
25
    REAL :: buffer_conc(1:anzKomponenten)
26
    buffer_conc = solveCConvert ()
27
    if (any(buffer_conc .ne. (/(real(i), i = 1, anzKomponenten)/))) &
28
          call abort ()
29
  END SUBROUTINE outDiffKoeff
30
 
31
  program missing_ref
32
    USE MODULE_CONC
33
    call outDiffKoeff
34
! Now set anzKomponenten to a value that would cause a segfault if
35
! buffer_conc and solveCConvert did not have the correct allocation
36
! of memory.
37
    anzKomponenten = 5000
38
    call outDiffKoeff
39
  end program missing_ref
40
 
41
  FUNCTION solveCConvert ()
42
    USE MODULE_CONC, ONLY: anzKomponenten
43
    REAL :: solveCConvert(1:anzKomponenten)
44
    solveCConvert = (/(real(i), i = 1, anzKomponenten)/)
45
  END FUNCTION solveCConvert
46
 
47
! { dg-final { cleanup-modules "MODULE_CONC MODULE_THERMOCALC" } }

powered by: WebSVN 2.1.0

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