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.
7 ! Based on the testcase in the PR.
10 INTEGER, SAVE :: anzKomponenten
= 2
11 END MODULE MODULE_CONC
13 MODULE MODULE_THERMOCALC
15 FUNCTION solveCConvert ()
16 USE MODULE_CONC
, ONLY
: anzKomponenten
17 REAL :: solveCConvert(1:anzKomponenten
)
18 END FUNCTION solveCConvert
20 END MODULE MODULE_THERMOCALC
22 SUBROUTINE outDiffKoeff
25 REAL :: buffer_conc(1:anzKomponenten
)
26 buffer_conc
= solveCConvert ()
27 if (any(buffer_conc
.ne
. (/(real(i
), i
= 1, anzKomponenten
)/))) &
29 END SUBROUTINE 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
39 end program missing_ref
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
47 ! { dg-final { cleanup-modules "MODULE_CONC MODULE_THERMOCALC" } }