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

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-old/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [unused_artificial_dummies_1.f90] - Diff between revs 154 and 816

Go to most recent revision | Only display areas with differences | Details | Blame | View Log

Rev 154 Rev 816
! { dg-do compile }
! { dg-do compile }
! { dg-options "-Wunused-variable -Wunused-parameter" }
! { dg-options "-Wunused-variable -Wunused-parameter" }
! This tests the fix for PR18111 in which some artificial declarations
! This tests the fix for PR18111 in which some artificial declarations
! were being listed as unused parameters:
! were being listed as unused parameters:
! (i) Array dummies, where a copy is made;
! (i) Array dummies, where a copy is made;
! (ii) The dummies of "entry thunks" (ie. the articial procedures that
! (ii) The dummies of "entry thunks" (ie. the articial procedures that
! represent ENTRYs and call the "entry_master" function; and
! represent ENTRYs and call the "entry_master" function; and
! (iii) The __entry parameter of the entry_master function, which
! (iii) The __entry parameter of the entry_master function, which
! indentifies the calling entry thunk.
! indentifies the calling entry thunk.
! All of these have DECL_ARTIFICIAL (tree) set.
! All of these have DECL_ARTIFICIAL (tree) set.
!
!
! Contributed by Paul Thomas  
! Contributed by Paul Thomas  
!
!
module foo
module foo
  implicit none
  implicit none
contains
contains
!This is the original problem
!This is the original problem
  subroutine bar(arg1, arg2, arg3, arg4, arg5)
  subroutine bar(arg1, arg2, arg3, arg4, arg5)
    character(len=80), intent(in) :: arg1
    character(len=80), intent(in) :: arg1
    character(len=80), dimension(:), intent(in) :: arg2
    character(len=80), dimension(:), intent(in) :: arg2
    integer, dimension(arg4), intent(in) :: arg3
    integer, dimension(arg4), intent(in) :: arg3
    integer, intent(in) :: arg4
    integer, intent(in) :: arg4
    character(len=arg4), intent(in) :: arg5
    character(len=arg4), intent(in) :: arg5
    print *, arg1, arg2, arg3, arg4, arg5
    print *, arg1, arg2, arg3, arg4, arg5
  end subroutine bar
  end subroutine bar
! This ICED with the first version of the fix because gfc_build_dummy_array_decl
! This ICED with the first version of the fix because gfc_build_dummy_array_decl
! sometimes NULLS sym->backend_decl; taken from aliasing_dummy_1.f90
! sometimes NULLS sym->backend_decl; taken from aliasing_dummy_1.f90
  subroutine foo1 (slist, i)
  subroutine foo1 (slist, i)
    character(*), dimension(*) :: slist
    character(*), dimension(*) :: slist
    integer i
    integer i
    write (slist(i), '(2hi=,i3)') i
    write (slist(i), '(2hi=,i3)') i
  end subroutine foo1
  end subroutine foo1
! This tests the additions to the fix that prevent the dummies of entry thunks
! This tests the additions to the fix that prevent the dummies of entry thunks
! and entry_master __entry parameters from being listed as unused.
! and entry_master __entry parameters from being listed as unused.
  function f1 (a)
  function f1 (a)
    integer, dimension (2, 2) :: a, b, f1, e1
    integer, dimension (2, 2) :: a, b, f1, e1
    f1 (:, :) = 15 + a
    f1 (:, :) = 15 + a
    return
    return
  entry e1 (b)
  entry e1 (b)
    e1 (:, :) = 42 + b
    e1 (:, :) = 42 + b
  end function
  end function
end module foo
end module foo
! { dg-final { cleanup-modules "foo" } }
! { dg-final { cleanup-modules "foo" } }
 
 

powered by: WebSVN 2.1.0

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