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.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [keyword_symbol_1.f90] - Diff between revs 149 and 154

Only display areas with differences | Details | Blame | View Log

Rev 149 Rev 154
! ' dg-do compile }
! ' dg-do compile }
! This tests the fix for PR28526, in which a public interface named
! This tests the fix for PR28526, in which a public interface named
! 'end' would be treated as a variable because the matcher tried
! 'end' would be treated as a variable because the matcher tried
! 'END INTERFACE' as an assignment and left the symbol modified in
! 'END INTERFACE' as an assignment and left the symbol modified in
! failing. The various pitfalls that were encountered in developing
! failing. The various pitfalls that were encountered in developing
! the fix are checked here.
! the fix are checked here.
!
!
! Contributed by Paul Thomas  
! Contributed by Paul Thomas  
!
!
module blahblah
module blahblah
  public function, end
  public function, end
! The original PR from Yusuke IGUCHI 
! The original PR from Yusuke IGUCHI 
  interface end
  interface end
    module procedure foo1
    module procedure foo1
  end interface
  end interface
! A contribution to the PR from Tobias Schlueter  
! A contribution to the PR from Tobias Schlueter  
  interface function
  interface function
     module procedure foo2 ! { dg-error "is neither function nor" }
     module procedure foo2 ! { dg-error "is neither function nor" }
  end interface
  end interface
  interface function
  interface function
     module procedure foo3
     module procedure foo3
  end interface
  end interface
  interface
  interface
    function foo4 ()
    function foo4 ()
      real foo4
      real foo4
      x = 1.0          ! { dg-error "in INTERFACE" }
      x = 1.0          ! { dg-error "in INTERFACE" }
    end function foo4
    end function foo4
  end interface
  end interface
  interface
  interface
    x = 2.0            ! { dg-error "in INTERFACE block" }
    x = 2.0            ! { dg-error "in INTERFACE block" }
    function foo5 ()
    function foo5 ()
      real foo5
      real foo5
    end function foo5
    end function foo5
  end interface
  end interface
  x = 3.0              ! { dg-error "in MODULE" }
  x = 3.0              ! { dg-error "in MODULE" }
contains
contains
  subroutine foo1
  subroutine foo1
  end subroutine foo1
  end subroutine foo1
  function foo2        ! { dg-error "Expected formal argument list" }
  function foo2        ! { dg-error "Expected formal argument list" }
    foo2 = 0           ! { dg-error "already been host associated" }
    foo2 = 0           ! { dg-error "already been host associated" }
  end function foo2    ! { dg-error "Expecting END MODULE" }
  end function foo2    ! { dg-error "Expecting END MODULE" }
  function foo3 ()
  function foo3 ()
    real foo3
    real foo3
  end function foo3
  end function foo3
  x = 4.0              ! { dg-error "in CONTAINS section" }
  x = 4.0              ! { dg-error "in CONTAINS section" }
end module blahblah
end module blahblah
 
 

powered by: WebSVN 2.1.0

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