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/] [used_before_typed_6.f90] - Rev 399

Go to most recent revision | Compare with Previous | Blame | View Log

! { dg-do compile }
! { dg-options "-std=gnu" }

! Allow legacy code to work even if not only a single symbol is used as
! expression but a basic arithmetic expression.

SUBROUTINE test (n, m)
  IMPLICIT NONE

  ! These should go fine.
  INTEGER :: arr1(n + 1) ! { dg-bogus "used before it is typed" }
  INTEGER :: arr2(n / (2 * m**5)) ! { dg-bogus "used before it is typed" }

  ! These should fail for obvious reasons.
  INTEGER :: arr3(n * 1.1) ! { dg-error "must be of INTEGER type" }
  INTEGER :: arr4(REAL (m)) ! { dg-error "used before it is typed" }
  INTEGER :: arr5(SIN (m)) ! { dg-error "used before it is typed" }

  INTEGER :: n, m
END SUBROUTINE test

Go to most recent revision | 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.