view gcc/testsuite/gfortran.dg/deferred_character_13.f90 @ 152:2b5abeee2509

update gcc11
author anatofuz
date Mon, 25 May 2020 07:50:57 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! { dg-do run }
!
! Tests the fix for PR49630 comment #3.
!
! Contributed by Janus Weil  <janus@gcc.gnu.org>
!
module abc
  implicit none

  type::abc_type
   contains
     procedure::abc_function
  end type abc_type

contains

  function abc_function(this)
    class(abc_type),intent(in)::this
    character(:),allocatable::abc_function
    allocate(abc_function,source="hello")
  end function abc_function

  subroutine do_something(this)
    class(abc_type),intent(in)::this
    if (this%abc_function() .ne. "hello") STOP 1
  end subroutine do_something

end module abc


  use abc
  type(abc_type) :: a
  call do_something(a)
end