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

Subversion Repositories openrisc_me

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [assumed_shape_ranks_2.f90] - Diff between revs 149 and 154

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

Rev 149 Rev 154
! { dg-do run }
! { dg-do run }
! Tests the fix for the regression PR26716.
! Tests the fix for the regression PR26716.
! Test contributed by Martin Reinecke  
! Test contributed by Martin Reinecke  
!
!
module mod1
module mod1
  implicit none
  implicit none
  interface foo
  interface foo
     module procedure foo1, foo2
     module procedure foo1, foo2
  end interface
  end interface
contains
contains
  subroutine foo1(bar, i)
  subroutine foo1(bar, i)
    real bar
    real bar
    integer i
    integer i
    i = 1
    i = 1
   end subroutine
   end subroutine
  subroutine foo2(bar, i)
  subroutine foo2(bar, i)
    real bar(3)
    real bar(3)
    integer i
    integer i
    i = 2
    i = 2
  end subroutine
  end subroutine
end module mod1
end module mod1
  use mod1
  use mod1
  implicit none
  implicit none
  real bar(3)
  real bar(3)
  integer i
  integer i
  i = 0
  i = 0
  call foo (1e0, i)
  call foo (1e0, i)
  if (i .ne. 1) call abort ()
  if (i .ne. 1) call abort ()
  i = 0
  i = 0
  call foo (bar(1), i)
  call foo (bar(1), i)
  if (i .ne. 1) call abort ()
  if (i .ne. 1) call abort ()
  i = 0
  i = 0
  call foo (bar, i)
  call foo (bar, i)
  if (i .ne. 2) call abort ()
  if (i .ne. 2) call abort ()
end
end
! { dg-final { cleanup-modules "mod1" } }
! { dg-final { cleanup-modules "mod1" } }
 
 

powered by: WebSVN 2.1.0

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