URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [elemental_subroutine_6.f90] - Rev 801
Go to most recent revision | Compare with Previous | Blame | View Log
! { dg-do compile }! PR35184 ICE in gfc_conv_array_index_offsetMODULE fooTYPE, PUBLIC :: barPRIVATEREAL :: valueEND TYPE barINTERFACE ASSIGNMENT (=)MODULE PROCEDURE assign_barEND INTERFACE ASSIGNMENT (=)CONTAINSELEMENTAL SUBROUTINE assign_bar (to, from)TYPE(bar), INTENT(OUT) :: toTYPE(bar), INTENT(IN) :: fromto%value= from%valueEND SUBROUTINESUBROUTINE my_sub (in, out)IMPLICIT NONETYPE(bar), DIMENSION(:,:), POINTER :: inTYPE(bar), DIMENSION(:,:), POINTER :: outALLOCATE( out(1:42, 1:42) )out(1, 1:42) = in(1, 1:42)END SUBROUTINEEND MODULE foo! { dg-final { cleanup-modules "foo" } }
Go to most recent revision | Compare with Previous | Blame | View Log
