URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [used_interface_ref.f90] - Rev 708
Go to most recent revision | Compare with Previous | Blame | View Log
! { dg-do run }! Tests the fix for PR26393, in which an ICE would occur in trans-decl.c! (gfc_get_symbol_decl) because anzKomponenten is not referenced in the! interface for solveCConvert. The solution was to assert that the symbol! is either referenced or in an interface body.!! Based on the testcase in the PR.!MODULE MODULE_CONCINTEGER, SAVE :: anzKomponenten = 2END MODULE MODULE_CONCMODULE MODULE_THERMOCALCINTERFACEFUNCTION solveCConvert ()USE MODULE_CONC, ONLY: anzKomponentenREAL :: solveCConvert(1:anzKomponenten)END FUNCTION solveCConvertEND INTERFACEEND MODULE MODULE_THERMOCALCSUBROUTINE outDiffKoeffUSE MODULE_CONCUSE MODULE_THERMOCALCREAL :: buffer_conc(1:anzKomponenten)buffer_conc = solveCConvert ()if (any(buffer_conc .ne. (/(real(i), i = 1, anzKomponenten)/))) &call abort ()END SUBROUTINE outDiffKoeffprogram missing_refUSE MODULE_CONCcall outDiffKoeff! Now set anzKomponenten to a value that would cause a segfault if! buffer_conc and solveCConvert did not have the correct allocation! of memory.anzKomponenten = 5000call outDiffKoeffend program missing_refFUNCTION solveCConvert ()USE MODULE_CONC, ONLY: anzKomponentenREAL :: solveCConvert(1:anzKomponenten)solveCConvert = (/(real(i), i = 1, anzKomponenten)/)END FUNCTION solveCConvert! { dg-final { cleanup-modules "module_conc module_thermocalc" } }
Go to most recent revision | Compare with Previous | Blame | View Log
