OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [use_only_3.f90] - Rev 694

Compare with Previous | Blame | View Log

! { dg-do compile }
! This tests the patch for PR34975, in which 'n', 'ipol', and 'i' would be
! determined to have 'no IMPLICIT type'.  It turned out to be fiendishly
! difficult to write a testcase for this PR because even the smallest changes
! would make the bug disappear.  This is the testcase provided in the PR, except
! that all the modules are put in 'use_only_3.inc' in the same order as the
! makefile.  Even this has an effect; only 'n' is now determined to be
! improperly typed.  All this is due to the richness of the symtree and the
! way in which the renaming inserted new symtree entries.  Unless somenody can
! come up with a reduced version, this relatively large file will have to be added
! to the testsuite.  Fortunately, it only has to be comiled once:)
!  
! Reported by Tobias Burnus <burnus@gcc.gnu.org>
!
include 'use_only_3.inc'
subroutine dforceb(c0, i, betae, ipol, bec0, ctabin, gqq, gqqm, qmat, dq2, df)
  use gvecs
  use gvecw, only: ngw
  use parameters
  use electrons_base, only: nx => nbspx, n => nbsp, nspin, f
  use constants
  use cvan
  use ions_base
  use ions_base, only : nas => nax
  implicit none

  integer ipol, i, ctabin
  complex c0(n), betae, df,&
       &   gqq,gqqm,&
       &   qmat
  real bec0,&
       &   dq2,  gmes

 end subroutine dforceb
! { dg-final { cleanup-modules "cell_base cvan gvecs kinds" } }
! { dg-final { cleanup-modules "constants electrons_base gvecw parameters" } }
! { dg-final { cleanup-modules "control_flags electrons_nose ions_base" } }

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.