OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [argument_checking_5.f90] - Rev 302

Compare with Previous | Blame | View Log

! { dg-do compile }
!
! PR fortran/30940
program test
implicit none
interface
  subroutine foobar(x)
     integer,dimension(4) :: x
  end subroutine foobar
  subroutine arr(y)
     integer,dimension(1,2,1,2) :: y
  end subroutine arr
end interface

integer a(3), b(5)
call foobar(a) ! { dg-warning "contains too few elements" }
call foobar(b)
call foobar(b(1:3)) ! { dg-warning "contains too few elements" }
call foobar(b(1:5))
call foobar(b(1:5:2)) ! { dg-warning "contains too few elements" }
call foobar(b(2))
call foobar(b(3)) ! { dg-warning "Actual argument contains too few elements" }
call foobar(reshape(a(1:3),[2,1])) ! { dg-warning "contains too few elements" }
call foobar(reshape(b(2:5),[2,2]))

call arr(a) ! { dg-warning "contains too few elements" }
call arr(b)
call arr(b(1:3)) ! { dg-warning "contains too few elements" }
call arr(b(1:5))
call arr(b(1:5:2)) ! { dg-warning "contains too few elements" }
call arr(b(2))
call arr(b(3)) ! { dg-warning "contains too few elements" }
call arr(reshape(a(1:3),[2,1])) ! { dg-warning "contains too few elements" }
call arr(reshape(b(2:5),[2,2]))
end program test

Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

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