URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [actual_array_constructor_1.f90] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do run }! Test the fix by HJ Lu for PR23634 and friends. All involve the ICE! that arose from a character array constructor usedas an actual! argument.!! The various parts of this test are taken from the PRs.!! Test PR26491module globalpublic p, lineinterface pmodule procedure pend interfacecharacter(128) :: line = 'abcdefghijklmnopqrstuvwxyz'containssubroutine p()character(128) :: wordword = linecall redirect_((/word/))end subroutinesubroutine redirect_ (ch)character(*) :: ch(:)if (ch(1) /= line) call abort ()end subroutine redirect_end module global! Test PR26550module my_moduleimplicit nonetype pointreal :: xend type pointtype(point), pointer, public :: stdin => NULL()containssubroutine my_p(w)character(128) :: wcall r(stdin,(/w/))end subroutine my_psubroutine r(ptr, io)use globaltype(point), pointer :: ptrcharacter(128) :: io(:)if (associated (ptr)) call abort ()if (io(1) .ne. line) call abort ()end subroutine rend module my_moduleprogram mainuse globaluse my_moduleinteger :: i(6) = (/1,6,3,4,5,2/)character (6) :: a = 'hello ', tcharacter(len=1) :: s(6) = (/'g','g','d','d','a','o'/)equivalence (s, t)call option_stopwatch_s (a) ! Call test of PR25619call p () ! Call test of PR26491call my_p (line) ! Call test of PR26550! Test Vivek Rao's bug, as reported in PR25619.s = s(i)call option_stopwatch_a ((/a,'hola! ', t/))contains! Test PR23634subroutine option_stopwatch_s(a)character (*), intent(in) :: acharacter (len=len(a)) :: bb = 'hola! 'call option_stopwatch_a((/a, b, 'goddag'/))end subroutine option_stopwatch_ssubroutine option_stopwatch_a (a)character (*) :: a(:)if (any (a .ne. (/'hello ','hola! ','goddag'/))) call abort ()end subroutine option_stopwatch_aend program main! { dg-final { cleanup-modules "global my_module" } }
