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

Subversion Repositories openrisc

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

Compare with Previous | Blame | View Log

! { dg-do run }
!
! PR fortran/51758
!
! Contributed by Mikael Morin
!
! Check whether passing NULL() to an elemental procedure works,
! where NULL() denotes an absent optional argument.
!
program p

  integer :: a(2)
  integer :: b

  a = 0
  a = foo((/ 1, 1 /), null())
!  print *, a
  if (any(a /= 2)) call abort

  a = 0
  a = bar((/ 1, 1 /), null())
!  print *, a
  if (any(a /= 2)) call abort

  b = 0
  b = bar(1, null())
!  print *, b
  if (b /= 2) call abort

contains

  function foo(a, b)
    integer           :: a(:)
    integer, optional :: b(:)
    integer           :: foo(size(a))

    if (present(b)) call abort

    foo = 2
  end function foo

  elemental function bar(a, b)
    integer, intent(in)           :: a
    integer, intent(in), optional :: b
    integer                       :: bar

    bar = 2

    if (present(b)) bar = 1

  end function bar

end program p

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.