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

Subversion Repositories openrisc

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

Go to most recent revision | Compare with Previous | Blame | View Log

! { dg-do run }
! Tests the fix for PR38602, a regression caused by a modification
! to the nulling of INTENT_OUT dummies with allocatable components
! that caused a segfault with optional arguments.
!
! Contributed by David Kinniburgh <davidkinniburgh@yahoo.co.uk>
!
program test_iso
  type ivs
     character(LEN=1), dimension(:), allocatable :: chars
  end type ivs
  type(ivs) :: v_str
  integer :: i
  call foo(v_str, i)
  if (v_str%chars(1) .ne. "a") call abort
  if (i .ne. 0) call abort
  call foo(flag = i)
  if (i .ne. 1) call abort
contains
  subroutine foo (arg, flag)
    type(ivs), optional, intent(out) :: arg
    integer :: flag
    if (present(arg)) then
      arg = ivs([(char(i+96), i = 1,10)])
      flag = 0
    else
      flag = 1
    end if
  end subroutine
end

Go to most recent revision | 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.